OSDN Git Service

* Makefile.in (reload1.o-warn): Remove.
[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-2007, 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 2,  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 COPYING.  If not, write --
19 -- to  the  Free Software Foundation,  51  Franklin  Street,  Fifth  Floor, --
20 -- Boston, MA 02110-1301, USA.                                              --
21 --                                                                          --
22 -- GNAT was originally developed  by the GNAT team at  New York University. --
23 -- Extensive contributions were provided by Ada Core Technologies Inc.      --
24 --                                                                          --
25 ------------------------------------------------------------------------------
26
27 with Atree;    use Atree;
28 with Checks;   use Checks;
29 with Debug;    use Debug;
30 with Einfo;    use Einfo;
31 with Elists;   use Elists;
32 with Errout;   use Errout;
33 with Expander; use Expander;
34 with Exp_Ch6;  use Exp_Ch6;
35 with Exp_Ch7;  use Exp_Ch7;
36 with Exp_Tss;  use Exp_Tss;
37 with Exp_Util; use Exp_Util;
38 with Fname;    use Fname;
39 with Freeze;   use Freeze;
40 with Itypes;   use Itypes;
41 with Lib.Xref; use Lib.Xref;
42 with Layout;   use Layout;
43 with Namet;    use Namet;
44 with Lib;      use Lib;
45 with Nlists;   use Nlists;
46 with Nmake;    use Nmake;
47 with Opt;      use Opt;
48 with Output;   use Output;
49 with Rtsfind;  use Rtsfind;
50 with Sem;      use Sem;
51 with Sem_Cat;  use Sem_Cat;
52 with Sem_Ch3;  use Sem_Ch3;
53 with Sem_Ch4;  use Sem_Ch4;
54 with Sem_Ch5;  use Sem_Ch5;
55 with Sem_Ch8;  use Sem_Ch8;
56 with Sem_Ch10; use Sem_Ch10;
57 with Sem_Ch12; use Sem_Ch12;
58 with Sem_Disp; use Sem_Disp;
59 with Sem_Dist; use Sem_Dist;
60 with Sem_Elim; use Sem_Elim;
61 with Sem_Eval; use Sem_Eval;
62 with Sem_Mech; use Sem_Mech;
63 with Sem_Prag; use Sem_Prag;
64 with Sem_Res;  use Sem_Res;
65 with Sem_Util; use Sem_Util;
66 with Sem_Type; use Sem_Type;
67 with Sem_Warn; use Sem_Warn;
68 with Sinput;   use Sinput;
69 with Stand;    use Stand;
70 with Sinfo;    use Sinfo;
71 with Sinfo.CN; use Sinfo.CN;
72 with Snames;   use Snames;
73 with Stringt;  use Stringt;
74 with Style;
75 with Stylesw;  use Stylesw;
76 with Tbuild;   use Tbuild;
77 with Uintp;    use Uintp;
78 with Urealp;   use Urealp;
79 with Validsw;  use Validsw;
80
81 package body Sem_Ch6 is
82
83    Enable_New_Return_Processing : constant Boolean := True;
84    --  ??? This flag is temporary. False causes the compiler to use the old
85    --  version of Analyze_Return_Statement; True, the new version, which does
86    --  not yet work. You probably want this to match the corresponding thing
87    --  in exp_ch5.adb.
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_A_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_A_Return_Statement.
107    --  Called when the return statement 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_Generic_Subprogram_Body (N : Node_Id; Gen_Id : Entity_Id);
115    --  Analyze a generic subprogram body. N is the body to be analyzed, and
116    --  Gen_Id is the defining entity Id for the corresponding spec.
117
118    procedure Build_Body_To_Inline (N : Node_Id; Subp : Entity_Id);
119    --  If a subprogram has pragma Inline and inlining is active, use generic
120    --  machinery to build an unexpanded body for the subprogram. This body is
121    --  subsequenty used for inline expansions at call sites. If subprogram can
122    --  be inlined (depending on size and nature of local declarations) this
123    --  function returns true. Otherwise subprogram body is treated normally.
124    --  If proper warnings are enabled and the subprogram contains a construct
125    --  that cannot be inlined, the offending construct is flagged accordingly.
126
127    procedure Check_Conformance
128      (New_Id                   : Entity_Id;
129       Old_Id                   : Entity_Id;
130       Ctype                    : Conformance_Type;
131       Errmsg                   : Boolean;
132       Conforms                 : out Boolean;
133       Err_Loc                  : Node_Id := Empty;
134       Get_Inst                 : Boolean := False;
135       Skip_Controlling_Formals : Boolean := False);
136    --  Given two entities, this procedure checks that the profiles associated
137    --  with these entities meet the conformance criterion given by the third
138    --  parameter. If they conform, Conforms is set True and control returns
139    --  to the caller. If they do not conform, Conforms is set to False, and
140    --  in addition, if Errmsg is True on the call, proper messages are output
141    --  to complain about the conformance failure. If Err_Loc is non_Empty
142    --  the error messages are placed on Err_Loc, if Err_Loc is empty, then
143    --  error messages are placed on the appropriate part of the construct
144    --  denoted by New_Id. If Get_Inst is true, then this is a mode conformance
145    --  against a formal access-to-subprogram type so Get_Instance_Of must
146    --  be called.
147
148    procedure Check_Overriding_Indicator
149      (Subp            : Entity_Id;
150       Overridden_Subp : Entity_Id := Empty);
151    --  Verify the consistency of an overriding_indicator given for subprogram
152    --  declaration, body, renaming, or instantiation. Overridden_Subp is set
153    --  if the scope into which we are introducing the subprogram contains a
154    --  type-conformant subprogram that becomes hidden by the new subprogram.
155
156    procedure Check_Subprogram_Order (N : Node_Id);
157    --  N is the N_Subprogram_Body node for a subprogram. This routine applies
158    --  the alpha ordering rule for N if this ordering requirement applicable.
159
160    procedure Check_Returns
161      (HSS  : Node_Id;
162       Mode : Character;
163       Err  : out Boolean;
164       Proc : Entity_Id := Empty);
165    --  Called to check for missing return statements in a function body, or for
166    --  returns present in a procedure body which has No_Return set. HSS is the
167    --  handled statement sequence for the subprogram body. This procedure
168    --  checks all flow paths to make sure they either have return (Mode = 'F',
169    --  used for functions) or do not have a return (Mode = 'P', used for
170    --  No_Return procedures). The flag Err is set if there are any control
171    --  paths not explicitly terminated by a return in the function case, and is
172    --  True otherwise. Proc is the entity for the procedure case and is used
173    --  in posting the warning message.
174
175    procedure Enter_Overloaded_Entity (S : Entity_Id);
176    --  This procedure makes S, a new overloaded entity, into the first visible
177    --  entity with that name.
178
179    procedure Install_Entity (E : Entity_Id);
180    --  Make single entity visible. Used for generic formals as well
181
182    procedure Install_Formals (Id : Entity_Id);
183    --  On entry to a subprogram body, make the formals visible. Note that
184    --  simply placing the subprogram on the scope stack is not sufficient:
185    --  the formals must become the current entities for their names.
186
187    function Is_Non_Overriding_Operation
188      (Prev_E : Entity_Id;
189       New_E  : Entity_Id) return Boolean;
190    --  Enforce the rule given in 12.3(18): a private operation in an instance
191    --  overrides an inherited operation only if the corresponding operation
192    --  was overriding in the generic. This can happen for primitive operations
193    --  of types derived (in the generic unit) from formal private or formal
194    --  derived types.
195
196    procedure Make_Inequality_Operator (S : Entity_Id);
197    --  Create the declaration for an inequality operator that is implicitly
198    --  created by a user-defined equality operator that yields a boolean.
199
200    procedure May_Need_Actuals (Fun : Entity_Id);
201    --  Flag functions that can be called without parameters, i.e. those that
202    --  have no parameters, or those for which defaults exist for all parameters
203
204    procedure Reference_Body_Formals (Spec : Entity_Id; Bod : Entity_Id);
205    --  If there is a separate spec for a subprogram or generic subprogram, the
206    --  formals of the body are treated as references to the corresponding
207    --  formals of the spec. This reference does not count as an actual use of
208    --  the formal, in order to diagnose formals that are unused in the body.
209
210    procedure Set_Formal_Validity (Formal_Id : Entity_Id);
211    --  Formal_Id is an formal parameter entity. This procedure deals with
212    --  setting the proper validity status for this entity, which depends
213    --  on the kind of parameter and the validity checking mode.
214
215    --------------------------------
216    -- Analyze_A_Return_Statement --
217    --------------------------------
218
219    procedure Analyze_A_Return_Statement (N : Node_Id) is
220       --  ???This should be called Analyze_Return_Statement, and
221       --  Analyze_Return_Statement should be called
222       --  Analyze_Simple_Return_Statement!
223
224       pragma Assert (Nkind (N) = N_Return_Statement
225                      or else Nkind (N) = N_Extended_Return_Statement);
226
227       Returns_Object : constant Boolean :=
228         Nkind (N) = N_Extended_Return_Statement
229          or else
230            (Nkind (N) = N_Return_Statement and then Present (Expression (N)));
231
232       --  True if we're returning something; that is, "return <expression>;"
233       --  or "return Result : T [:= ...]". False for "return;".
234       --  Used for error checking: If Returns_Object is True, N should apply
235       --  to a function body; otherwise N should apply to a procedure body,
236       --  entry body, accept statement, or extended return statement.
237
238       function Find_What_It_Applies_To return Entity_Id;
239       --  Find the entity representing the innermost enclosing body, accept
240       --  statement, or extended return statement. If the result is a
241       --  callable construct or extended return statement, then this will be
242       --  the value of the Return_Applies_To attribute. Otherwise, the program
243       --  is illegal. See RM-6.5(4/2). I am disinclined to call this
244       --  Find_The_Construct_To_Which_This_Return_Statement_Applies. ;-)
245
246       -----------------------------
247       -- Find_What_It_Applies_To --
248       -----------------------------
249
250       function Find_What_It_Applies_To return Entity_Id is
251          Result : Entity_Id := Empty;
252
253       begin
254          --  Loop outward through the Scope_Stack, skipping blocks and loops
255
256          for J in reverse 0 .. Scope_Stack.Last loop
257             Result := Scope_Stack.Table (J).Entity;
258             exit when Ekind (Result) /= E_Block and then
259                       Ekind (Result) /= E_Loop;
260          end loop;
261
262          pragma Assert (Present (Result));
263          return Result;
264
265       end Find_What_It_Applies_To;
266
267       Scope_Id   : constant Entity_Id   := Find_What_It_Applies_To;
268       Kind       : constant Entity_Kind := Ekind (Scope_Id);
269
270       Loc        : constant Source_Ptr  := Sloc (N);
271       Stm_Entity : constant Entity_Id   :=
272                      New_Internal_Entity
273                        (E_Return_Statement, Current_Scope, Loc, 'R');
274
275    --  Start of processing for Analyze_A_Return_Statement
276
277    begin
278
279       Set_Return_Statement_Entity (N, Stm_Entity);
280
281       Set_Etype (Stm_Entity, Standard_Void_Type);
282       Set_Return_Applies_To (Stm_Entity, Scope_Id);
283
284       --  Place the Return entity on scope stack, to simplify enforcement
285       --  of 6.5 (4/2): an inner return statement will apply to this extended
286       --  return.
287
288       if Nkind (N) = N_Extended_Return_Statement then
289          Push_Scope (Stm_Entity);
290       end if;
291
292       --  Check that pragma No_Return is obeyed:
293
294       if No_Return (Scope_Id) then
295          Error_Msg_N ("RETURN statement not allowed (No_Return)", N);
296       end if;
297
298       --  Check that functions return objects, and other things do not:
299
300       if Kind = E_Function or else Kind = E_Generic_Function then
301          if not Returns_Object then
302             Error_Msg_N ("missing expression in return from function", N);
303          end if;
304
305       elsif Kind = E_Procedure or else Kind = E_Generic_Procedure then
306          if Returns_Object then
307             Error_Msg_N ("procedure cannot return value (use function)", N);
308          end if;
309
310       elsif Kind = E_Entry or else Kind = E_Entry_Family then
311          if Returns_Object then
312             if Is_Protected_Type (Scope (Scope_Id)) then
313                Error_Msg_N ("entry body cannot return value", N);
314             else
315                Error_Msg_N ("accept statement cannot return value", N);
316             end if;
317          end if;
318
319       elsif Kind = E_Return_Statement then
320
321          --  We are nested within another return statement, which must be an
322          --  extended_return_statement.
323
324          if Returns_Object then
325             Error_Msg_N
326               ("extended_return_statement cannot return value; " &
327                "use `""RETURN;""`", N);
328          end if;
329
330       else
331          Error_Msg_N ("illegal context for return statement", N);
332       end if;
333
334       if Kind = E_Function or else Kind = E_Generic_Function then
335          Analyze_Function_Return (N);
336       end if;
337
338       if Nkind (N) = N_Extended_Return_Statement then
339          End_Scope;
340       end if;
341
342       Check_Unreachable_Code (N);
343    end Analyze_A_Return_Statement;
344
345    ---------------------------------------------
346    -- Analyze_Abstract_Subprogram_Declaration --
347    ---------------------------------------------
348
349    procedure Analyze_Abstract_Subprogram_Declaration (N : Node_Id) is
350       Designator : constant Entity_Id :=
351                      Analyze_Subprogram_Specification (Specification (N));
352       Scop       : constant Entity_Id := Current_Scope;
353
354    begin
355       Generate_Definition (Designator);
356       Set_Is_Abstract_Subprogram (Designator);
357       New_Overloaded_Entity (Designator);
358       Check_Delayed_Subprogram (Designator);
359
360       Set_Categorization_From_Scope (Designator, Scop);
361
362       if Ekind (Scope (Designator)) = E_Protected_Type then
363          Error_Msg_N
364            ("abstract subprogram not allowed in protected type", N);
365       end if;
366
367       Generate_Reference_To_Formals (Designator);
368    end Analyze_Abstract_Subprogram_Declaration;
369
370    ----------------------------------------
371    -- Analyze_Extended_Return_Statement  --
372    ----------------------------------------
373
374    procedure Analyze_Extended_Return_Statement (N : Node_Id) is
375    begin
376       Analyze_A_Return_Statement (N);
377    end Analyze_Extended_Return_Statement;
378
379    ----------------------------
380    -- Analyze_Function_Call  --
381    ----------------------------
382
383    procedure Analyze_Function_Call (N : Node_Id) is
384       P      : constant Node_Id := Name (N);
385       L      : constant List_Id := Parameter_Associations (N);
386       Actual : Node_Id;
387
388    begin
389       Analyze (P);
390
391       --  A call of the form A.B (X) may be an Ada05 call, which is rewritten
392       --  as B (A, X). If the rewriting is successful, the call has been
393       --  analyzed and we just return.
394
395       if Nkind (P) = N_Selected_Component
396         and then Name (N) /= P
397         and then Is_Rewrite_Substitution (N)
398         and then Present (Etype (N))
399       then
400          return;
401       end if;
402
403       --  If error analyzing name, then set Any_Type as result type and return
404
405       if Etype (P) = Any_Type then
406          Set_Etype (N, Any_Type);
407          return;
408       end if;
409
410       --  Otherwise analyze the parameters
411
412       if Present (L) then
413          Actual := First (L);
414          while Present (Actual) loop
415             Analyze (Actual);
416             Check_Parameterless_Call (Actual);
417             Next (Actual);
418          end loop;
419       end if;
420
421       Analyze_Call (N);
422    end Analyze_Function_Call;
423
424    -----------------------------
425    -- Analyze_Function_Return --
426    -----------------------------
427
428    procedure Analyze_Function_Return (N : Node_Id) is
429       Loc        : constant Source_Ptr  := Sloc (N);
430       Stm_Entity : constant Entity_Id   := Return_Statement_Entity (N);
431       Scope_Id   : constant Entity_Id   := Return_Applies_To (Stm_Entity);
432
433       R_Type : constant Entity_Id   := Etype (Scope_Id);
434       --  Function result subtype
435
436       procedure Check_Limited_Return (Expr : Node_Id);
437       --  Check the appropriate (Ada 95 or Ada 2005) rules for returning
438       --  limited types. Used only for simple return statements.
439       --  Expr is the expression returned.
440
441       procedure Check_Return_Subtype_Indication (Obj_Decl : Node_Id);
442       --  Check that the return_subtype_indication properly matches the result
443       --  subtype of the function, as required by RM-6.5(5.1/2-5.3/2).
444
445       --------------------------
446       -- Check_Limited_Return --
447       --------------------------
448
449       procedure Check_Limited_Return (Expr : Node_Id) is
450       begin
451          --  Ada 2005 (AI-318-02): Return-by-reference types have been
452          --  removed and replaced by anonymous access results. This is an
453          --  incompatibility with Ada 95. Not clear whether this should be
454          --  enforced yet or perhaps controllable with special switch. ???
455
456          if Is_Limited_Type (R_Type)
457            and then Comes_From_Source (N)
458            and then not In_Instance_Body
459            and then not OK_For_Limited_Init_In_05 (Expr)
460          then
461             --  Error in Ada 2005
462
463             if Ada_Version >= Ada_05
464               and then not Debug_Flag_Dot_L
465               and then not GNAT_Mode
466             then
467                Error_Msg_N
468                  ("(Ada 2005) cannot copy object of a limited type " &
469                   "('R'M'-2005 6.5(5.5/2))", Expr);
470                if Is_Inherently_Limited_Type (R_Type) then
471                   Error_Msg_N
472                     ("\return by reference not permitted in Ada 2005", Expr);
473                end if;
474
475             --  Warn in Ada 95 mode, to give folks a heads up about this
476             --  incompatibility.
477
478             --  In GNAT mode, this is just a warning, to allow it to be
479             --  evilly turned off. Otherwise it is a real error.
480
481             elsif Warn_On_Ada_2005_Compatibility or GNAT_Mode then
482                if Is_Inherently_Limited_Type (R_Type) then
483                   Error_Msg_N
484                     ("return by reference not permitted in Ada 2005 " &
485                      "('R'M'-2005 6.5(5.5/2))?", Expr);
486                else
487                   Error_Msg_N
488                     ("cannot copy object of a limited type in Ada 2005 " &
489                      "('R'M'-2005 6.5(5.5/2))?", Expr);
490                end if;
491
492             --  Ada 95 mode, compatibility warnings disabled
493
494             else
495                return; --  skip continuation messages below
496             end if;
497
498             Error_Msg_N
499               ("\consider switching to return of access type", Expr);
500             Explain_Limited_Type (R_Type, Expr);
501          end if;
502       end Check_Limited_Return;
503
504       -------------------------------------
505       -- Check_Return_Subtype_Indication --
506       -------------------------------------
507
508       procedure Check_Return_Subtype_Indication (Obj_Decl : Node_Id) is
509          Return_Obj  : constant Node_Id   := Defining_Identifier (Obj_Decl);
510          R_Stm_Type  : constant Entity_Id := Etype (Return_Obj);
511          --  Subtype given in the extended return statement;
512          --  this must match R_Type.
513
514          Subtype_Ind : constant Node_Id :=
515                          Object_Definition (Original_Node (Obj_Decl));
516
517          R_Type_Is_Anon_Access :
518            constant Boolean :=
519              Ekind (R_Type) = E_Anonymous_Access_Subprogram_Type
520                or else
521              Ekind (R_Type) = E_Anonymous_Access_Protected_Subprogram_Type
522                or else
523              Ekind (R_Type) = E_Anonymous_Access_Type;
524          --  True if return type of the function is an anonymous access type
525          --  Can't we make Is_Anonymous_Access_Type in einfo ???
526
527          R_Stm_Type_Is_Anon_Access :
528            constant Boolean :=
529              Ekind (R_Stm_Type) = E_Anonymous_Access_Subprogram_Type
530                or else
531              Ekind (R_Stm_Type) = E_Anonymous_Access_Protected_Subprogram_Type
532                or else
533              Ekind (R_Stm_Type) = E_Anonymous_Access_Type;
534          --  True if type of the return object is an anonymous access type
535
536       begin
537          --  First, avoid cascade errors:
538
539          if Error_Posted (Obj_Decl) or else Error_Posted (Subtype_Ind) then
540             return;
541          end if;
542
543          --  "return access T" case; check that the return statement also has
544          --  "access T", and that the subtypes statically match:
545
546          if R_Type_Is_Anon_Access then
547             if R_Stm_Type_Is_Anon_Access then
548                if Base_Type (Designated_Type (R_Stm_Type)) /=
549                     Base_Type (Designated_Type (R_Type))
550                  or else not Subtypes_Statically_Match (R_Stm_Type, R_Type)
551                then
552                   Error_Msg_N
553                     ("subtype must statically match function result subtype",
554                      Subtype_Mark (Subtype_Ind));
555                end if;
556
557             else
558                Error_Msg_N ("must use anonymous access type", Subtype_Ind);
559             end if;
560
561          --  Subtype_indication case; check that the types are the same, and
562          --  statically match if appropriate:
563
564          elsif Base_Type (R_Stm_Type) = Base_Type (R_Type) then
565             if Is_Constrained (R_Type) then
566                if not Subtypes_Statically_Match (R_Stm_Type, R_Type) then
567                   Error_Msg_N
568                     ("subtype must statically match function result subtype",
569                      Subtype_Ind);
570                end if;
571             end if;
572
573          --  If the function's result type doesn't match the return object
574          --  entity's type, then we check for the case where the result type
575          --  is class-wide, and allow the declaration if the type of the object
576          --  definition matches the class-wide type. This prevents rejection
577          --  in the case where the object declaration is initialized by a call
578          --  to a build-in-place function with a specific result type and the
579          --  object entity had its type changed to that specific type. (Note
580          --  that the ARG believes that return objects should be allowed to
581          --  have a type covered by a class-wide result type in any case, so
582          --  once that relaxation is made (see AI05-32), the above check for
583          --  type compatibility should be changed to test Covers rather than
584          --  equality, and then the following special test will no longer be
585          --  needed. ???)
586
587          elsif Is_Class_Wide_Type (R_Type)
588            and then R_Type = Etype (Object_Definition (Obj_Decl))
589          then
590             null;
591
592          else
593             Error_Msg_N
594               ("wrong type for return_subtype_indication", Subtype_Ind);
595          end if;
596       end Check_Return_Subtype_Indication;
597
598       ---------------------
599       -- Local Variables --
600       ---------------------
601
602       Expr : Node_Id;
603
604    --  Start of processing for Analyze_Function_Return
605
606    begin
607       Set_Return_Present (Scope_Id);
608
609       if Nkind (N) = N_Return_Statement then
610          Expr := Expression (N);
611          Analyze_And_Resolve (Expr, R_Type);
612          Check_Limited_Return (Expr);
613
614       else
615          --  Analyze parts specific to extended_return_statement:
616
617          declare
618             Obj_Decl : constant Node_Id :=
619                          Last (Return_Object_Declarations (N));
620
621             HSS : constant Node_Id := Handled_Statement_Sequence (N);
622
623          begin
624             Expr := Expression (Obj_Decl);
625
626             --  Note: The check for OK_For_Limited_Init will happen in
627             --  Analyze_Object_Declaration; we treat it as a normal
628             --  object declaration.
629
630             Analyze (Obj_Decl);
631
632             Set_Is_Return_Object (Defining_Identifier (Obj_Decl));
633             Check_Return_Subtype_Indication (Obj_Decl);
634
635             if Present (HSS) then
636                Analyze (HSS);
637
638                if Present (Exception_Handlers (HSS)) then
639
640                   --  ???Has_Nested_Block_With_Handler needs to be set.
641                   --  Probably by creating an actual N_Block_Statement.
642                   --  Probably in Expand.
643
644                   null;
645                end if;
646             end if;
647
648             Check_References (Stm_Entity);
649          end;
650       end if;
651
652       if Present (Expr)
653         and then Present (Etype (Expr)) --  Could be False in case of errors.
654       then
655          --  Ada 2005 (AI-318-02): When the result type is an anonymous
656          --  access type, apply an implicit conversion of the expression
657          --  to that type to force appropriate static and run-time
658          --  accessibility checks.
659
660          if Ada_Version >= Ada_05
661            and then Ekind (R_Type) = E_Anonymous_Access_Type
662          then
663             Rewrite (Expr, Convert_To (R_Type, Relocate_Node (Expr)));
664             Analyze_And_Resolve (Expr, R_Type);
665          end if;
666
667          if (Is_Class_Wide_Type (Etype (Expr))
668               or else Is_Dynamically_Tagged (Expr))
669            and then not Is_Class_Wide_Type (R_Type)
670          then
671             Error_Msg_N
672               ("dynamically tagged expression not allowed!", Expr);
673          end if;
674
675          Apply_Constraint_Check (Expr, R_Type);
676
677          --  ??? A real run-time accessibility check is needed in cases
678          --  involving dereferences of access parameters. For now we just
679          --  check the static cases.
680
681          if (Ada_Version < Ada_05 or else Debug_Flag_Dot_L)
682            and then Is_Inherently_Limited_Type (Etype (Scope_Id))
683            and then Object_Access_Level (Expr) >
684                       Subprogram_Access_Level (Scope_Id)
685          then
686             Rewrite (N,
687               Make_Raise_Program_Error (Loc,
688                 Reason => PE_Accessibility_Check_Failed));
689             Analyze (N);
690
691             Error_Msg_N
692               ("cannot return a local value by reference?", N);
693             Error_Msg_NE
694               ("\& will be raised at run time?",
695                N, Standard_Program_Error);
696          end if;
697       end if;
698    end Analyze_Function_Return;
699
700    -------------------------------------
701    -- Analyze_Generic_Subprogram_Body --
702    -------------------------------------
703
704    procedure Analyze_Generic_Subprogram_Body
705      (N      : Node_Id;
706       Gen_Id : Entity_Id)
707    is
708       Gen_Decl : constant Node_Id     := Unit_Declaration_Node (Gen_Id);
709       Kind     : constant Entity_Kind := Ekind (Gen_Id);
710       Body_Id  : Entity_Id;
711       New_N    : Node_Id;
712       Spec     : Node_Id;
713
714    begin
715       --  Copy body and disable expansion while analyzing the generic For a
716       --  stub, do not copy the stub (which would load the proper body), this
717       --  will be done when the proper body is analyzed.
718
719       if Nkind (N) /= N_Subprogram_Body_Stub then
720          New_N := Copy_Generic_Node (N, Empty, Instantiating => False);
721          Rewrite (N, New_N);
722          Start_Generic;
723       end if;
724
725       Spec := Specification (N);
726
727       --  Within the body of the generic, the subprogram is callable, and
728       --  behaves like the corresponding non-generic unit.
729
730       Body_Id := Defining_Entity (Spec);
731
732       if Kind = E_Generic_Procedure
733         and then Nkind (Spec) /= N_Procedure_Specification
734       then
735          Error_Msg_N ("invalid body for generic procedure ", Body_Id);
736          return;
737
738       elsif Kind = E_Generic_Function
739         and then Nkind (Spec) /= N_Function_Specification
740       then
741          Error_Msg_N ("invalid body for generic function ", Body_Id);
742          return;
743       end if;
744
745       Set_Corresponding_Body (Gen_Decl, Body_Id);
746
747       if Has_Completion (Gen_Id)
748         and then Nkind (Parent (N)) /= N_Subunit
749       then
750          Error_Msg_N ("duplicate generic body", N);
751          return;
752       else
753          Set_Has_Completion (Gen_Id);
754       end if;
755
756       if Nkind (N) = N_Subprogram_Body_Stub then
757          Set_Ekind (Defining_Entity (Specification (N)), Kind);
758       else
759          Set_Corresponding_Spec (N, Gen_Id);
760       end if;
761
762       if Nkind (Parent (N)) = N_Compilation_Unit then
763          Set_Cunit_Entity (Current_Sem_Unit, Defining_Entity (N));
764       end if;
765
766       --  Make generic parameters immediately visible in the body. They are
767       --  needed to process the formals declarations. Then make the formals
768       --  visible in a separate step.
769
770       Push_Scope (Gen_Id);
771
772       declare
773          E         : Entity_Id;
774          First_Ent : Entity_Id;
775
776       begin
777          First_Ent := First_Entity (Gen_Id);
778
779          E := First_Ent;
780          while Present (E) and then not Is_Formal (E) loop
781             Install_Entity (E);
782             Next_Entity (E);
783          end loop;
784
785          Set_Use (Generic_Formal_Declarations (Gen_Decl));
786
787          --  Now generic formals are visible, and the specification can be
788          --  analyzed, for subsequent conformance check.
789
790          Body_Id := Analyze_Subprogram_Specification (Spec);
791
792          --  Make formal parameters visible
793
794          if Present (E) then
795
796             --  E is the first formal parameter, we loop through the formals
797             --  installing them so that they will be visible.
798
799             Set_First_Entity (Gen_Id, E);
800             while Present (E) loop
801                Install_Entity (E);
802                Next_Formal (E);
803             end loop;
804          end if;
805
806          --  Visible generic entity is callable within its own body
807
808          Set_Ekind          (Gen_Id,  Ekind (Body_Id));
809          Set_Ekind          (Body_Id, E_Subprogram_Body);
810          Set_Convention     (Body_Id, Convention (Gen_Id));
811          Set_Is_Obsolescent (Body_Id, Is_Obsolescent (Gen_Id));
812          Set_Scope          (Body_Id, Scope (Gen_Id));
813          Check_Fully_Conformant (Body_Id, Gen_Id, Body_Id);
814
815          if Nkind (N) = N_Subprogram_Body_Stub then
816
817             --  No body to analyze, so restore state of generic unit
818
819             Set_Ekind (Gen_Id, Kind);
820             Set_Ekind (Body_Id, Kind);
821
822             if Present (First_Ent) then
823                Set_First_Entity (Gen_Id, First_Ent);
824             end if;
825
826             End_Scope;
827             return;
828          end if;
829
830          --  If this is a compilation unit, it must be made visible explicitly,
831          --  because the compilation of the declaration, unlike other library
832          --  unit declarations, does not. If it is not a unit, the following
833          --  is redundant but harmless.
834
835          Set_Is_Immediately_Visible (Gen_Id);
836          Reference_Body_Formals (Gen_Id, Body_Id);
837
838          if Is_Child_Unit (Gen_Id) then
839             Generate_Reference (Gen_Id, Scope (Gen_Id), 'k', False);
840          end if;
841
842          Set_Actual_Subtypes (N, Current_Scope);
843          Analyze_Declarations (Declarations (N));
844          Check_Completion;
845          Analyze (Handled_Statement_Sequence (N));
846
847          Save_Global_References (Original_Node (N));
848
849          --  Prior to exiting the scope, include generic formals again (if any
850          --  are present) in the set of local entities.
851
852          if Present (First_Ent) then
853             Set_First_Entity (Gen_Id, First_Ent);
854          end if;
855
856          Check_References (Gen_Id);
857       end;
858
859       Process_End_Label (Handled_Statement_Sequence (N), 't', Current_Scope);
860       End_Scope;
861       Check_Subprogram_Order (N);
862
863       --  Outside of its body, unit is generic again
864
865       Set_Ekind (Gen_Id, Kind);
866       Generate_Reference (Gen_Id, Body_Id, 'b', Set_Ref => False);
867       Style.Check_Identifier (Body_Id, Gen_Id);
868       End_Generic;
869    end Analyze_Generic_Subprogram_Body;
870
871    -----------------------------
872    -- Analyze_Operator_Symbol --
873    -----------------------------
874
875    --  An operator symbol such as "+" or "and" may appear in context where the
876    --  literal denotes an entity name, such as "+"(x, y) or in context when it
877    --  is just a string, as in (conjunction = "or"). In these cases the parser
878    --  generates this node, and the semantics does the disambiguation. Other
879    --  such case are actuals in an instantiation, the generic unit in an
880    --  instantiation, and pragma arguments.
881
882    procedure Analyze_Operator_Symbol (N : Node_Id) is
883       Par : constant Node_Id := Parent (N);
884
885    begin
886       if        (Nkind (Par) = N_Function_Call and then N = Name (Par))
887         or else  Nkind (Par) = N_Function_Instantiation
888         or else (Nkind (Par) = N_Indexed_Component and then N = Prefix (Par))
889         or else (Nkind (Par) = N_Pragma_Argument_Association
890                    and then not Is_Pragma_String_Literal (Par))
891         or else  Nkind (Par) = N_Subprogram_Renaming_Declaration
892         or else  (Nkind (Par) = N_Attribute_Reference
893                    and then Attribute_Name (Par) /= Name_Value)
894       then
895          Find_Direct_Name (N);
896
897       else
898          Change_Operator_Symbol_To_String_Literal (N);
899          Analyze (N);
900       end if;
901    end Analyze_Operator_Symbol;
902
903    -----------------------------------
904    -- Analyze_Parameter_Association --
905    -----------------------------------
906
907    procedure Analyze_Parameter_Association (N : Node_Id) is
908    begin
909       Analyze (Explicit_Actual_Parameter (N));
910    end Analyze_Parameter_Association;
911
912    ----------------------------
913    -- Analyze_Procedure_Call --
914    ----------------------------
915
916    procedure Analyze_Procedure_Call (N : Node_Id) is
917       Loc     : constant Source_Ptr := Sloc (N);
918       P       : constant Node_Id    := Name (N);
919       Actuals : constant List_Id    := Parameter_Associations (N);
920       Actual  : Node_Id;
921       New_N   : Node_Id;
922
923       procedure Analyze_Call_And_Resolve;
924       --  Do Analyze and Resolve calls for procedure call
925
926       ------------------------------
927       -- Analyze_Call_And_Resolve --
928       ------------------------------
929
930       procedure Analyze_Call_And_Resolve is
931       begin
932          if Nkind (N) = N_Procedure_Call_Statement then
933             Analyze_Call (N);
934             Resolve (N, Standard_Void_Type);
935          else
936             Analyze (N);
937          end if;
938       end Analyze_Call_And_Resolve;
939
940    --  Start of processing for Analyze_Procedure_Call
941
942    begin
943       --  The syntactic construct: PREFIX ACTUAL_PARAMETER_PART can denote
944       --  a procedure call or an entry call. The prefix may denote an access
945       --  to subprogram type, in which case an implicit dereference applies.
946       --  If the prefix is an indexed component (without implicit defererence)
947       --  then the construct denotes a call to a member of an entire family.
948       --  If the prefix is a simple name, it may still denote a call to a
949       --  parameterless member of an entry family. Resolution of these various
950       --  interpretations is delicate.
951
952       Analyze (P);
953
954       --  If this is a call of the form Obj.Op, the call may have been
955       --  analyzed and possibly rewritten into a block, in which case
956       --  we are done.
957
958       if Analyzed (N) then
959          return;
960       end if;
961
962       --  If error analyzing prefix, then set Any_Type as result and return
963
964       if Etype (P) = Any_Type then
965          Set_Etype (N, Any_Type);
966          return;
967       end if;
968
969       --  Otherwise analyze the parameters
970
971       if Present (Actuals) then
972          Actual := First (Actuals);
973
974          while Present (Actual) loop
975             Analyze (Actual);
976             Check_Parameterless_Call (Actual);
977             Next (Actual);
978          end loop;
979       end if;
980
981       --  Special processing for Elab_Spec and Elab_Body calls
982
983       if Nkind (P) = N_Attribute_Reference
984         and then (Attribute_Name (P) = Name_Elab_Spec
985                    or else Attribute_Name (P) = Name_Elab_Body)
986       then
987          if Present (Actuals) then
988             Error_Msg_N
989               ("no parameters allowed for this call", First (Actuals));
990             return;
991          end if;
992
993          Set_Etype (N, Standard_Void_Type);
994          Set_Analyzed (N);
995
996       elsif Is_Entity_Name (P)
997         and then Is_Record_Type (Etype (Entity (P)))
998         and then Remote_AST_I_Dereference (P)
999       then
1000          return;
1001
1002       elsif Is_Entity_Name (P)
1003         and then Ekind (Entity (P)) /= E_Entry_Family
1004       then
1005          if Is_Access_Type (Etype (P))
1006            and then Ekind (Designated_Type (Etype (P))) = E_Subprogram_Type
1007            and then No (Actuals)
1008            and then Comes_From_Source (N)
1009          then
1010             Error_Msg_N ("missing explicit dereference in call", N);
1011          end if;
1012
1013          Analyze_Call_And_Resolve;
1014
1015       --  If the prefix is the simple name of an entry family, this is
1016       --  a parameterless call from within the task body itself.
1017
1018       elsif Is_Entity_Name (P)
1019         and then Nkind (P) = N_Identifier
1020         and then Ekind (Entity (P)) = E_Entry_Family
1021         and then Present (Actuals)
1022         and then No (Next (First (Actuals)))
1023       then
1024          --  Can be call to parameterless entry family. What appears to be the
1025          --  sole argument is in fact the entry index. Rewrite prefix of node
1026          --  accordingly. Source representation is unchanged by this
1027          --  transformation.
1028
1029          New_N :=
1030            Make_Indexed_Component (Loc,
1031              Prefix =>
1032                Make_Selected_Component (Loc,
1033                  Prefix => New_Occurrence_Of (Scope (Entity (P)), Loc),
1034                  Selector_Name => New_Occurrence_Of (Entity (P), Loc)),
1035              Expressions => Actuals);
1036          Set_Name (N, New_N);
1037          Set_Etype (New_N, Standard_Void_Type);
1038          Set_Parameter_Associations (N, No_List);
1039          Analyze_Call_And_Resolve;
1040
1041       elsif Nkind (P) = N_Explicit_Dereference then
1042          if Ekind (Etype (P)) = E_Subprogram_Type then
1043             Analyze_Call_And_Resolve;
1044          else
1045             Error_Msg_N ("expect access to procedure in call", P);
1046          end if;
1047
1048       --  The name can be a selected component or an indexed component that
1049       --  yields an access to subprogram. Such a prefix is legal if the call
1050       --  has parameter associations.
1051
1052       elsif Is_Access_Type (Etype (P))
1053         and then Ekind (Designated_Type (Etype (P))) = E_Subprogram_Type
1054       then
1055          if Present (Actuals) then
1056             Analyze_Call_And_Resolve;
1057          else
1058             Error_Msg_N ("missing explicit dereference in call ", N);
1059          end if;
1060
1061       --  If not an access to subprogram, then the prefix must resolve to the
1062       --  name of an entry, entry family, or protected operation.
1063
1064       --  For the case of a simple entry call, P is a selected component where
1065       --  the prefix is the task and the selector name is the entry. A call to
1066       --  a protected procedure will have the same syntax. If the protected
1067       --  object contains overloaded operations, the entity may appear as a
1068       --  function, the context will select the operation whose type is Void.
1069
1070       elsif Nkind (P) = N_Selected_Component
1071         and then (Ekind (Entity (Selector_Name (P))) = E_Entry
1072                     or else
1073                   Ekind (Entity (Selector_Name (P))) = E_Procedure
1074                     or else
1075                   Ekind (Entity (Selector_Name (P))) = E_Function)
1076       then
1077          Analyze_Call_And_Resolve;
1078
1079       elsif Nkind (P) = N_Selected_Component
1080         and then Ekind (Entity (Selector_Name (P))) = E_Entry_Family
1081         and then Present (Actuals)
1082         and then No (Next (First (Actuals)))
1083       then
1084          --  Can be call to parameterless entry family. What appears to be the
1085          --  sole argument is in fact the entry index. Rewrite prefix of node
1086          --  accordingly. Source representation is unchanged by this
1087          --  transformation.
1088
1089          New_N :=
1090            Make_Indexed_Component (Loc,
1091              Prefix => New_Copy (P),
1092              Expressions => Actuals);
1093          Set_Name (N, New_N);
1094          Set_Etype (New_N, Standard_Void_Type);
1095          Set_Parameter_Associations (N, No_List);
1096          Analyze_Call_And_Resolve;
1097
1098       --  For the case of a reference to an element of an entry family, P is
1099       --  an indexed component whose prefix is a selected component (task and
1100       --  entry family), and whose index is the entry family index.
1101
1102       elsif Nkind (P) = N_Indexed_Component
1103         and then Nkind (Prefix (P)) = N_Selected_Component
1104         and then Ekind (Entity (Selector_Name (Prefix (P)))) = E_Entry_Family
1105       then
1106          Analyze_Call_And_Resolve;
1107
1108       --  If the prefix is the name of an entry family, it is a call from
1109       --  within the task body itself.
1110
1111       elsif Nkind (P) = N_Indexed_Component
1112         and then Nkind (Prefix (P)) = N_Identifier
1113         and then Ekind (Entity (Prefix (P))) = E_Entry_Family
1114       then
1115          New_N :=
1116            Make_Selected_Component (Loc,
1117              Prefix => New_Occurrence_Of (Scope (Entity (Prefix (P))), Loc),
1118              Selector_Name => New_Occurrence_Of (Entity (Prefix (P)), Loc));
1119          Rewrite (Prefix (P), New_N);
1120          Analyze (P);
1121          Analyze_Call_And_Resolve;
1122
1123       --  Anything else is an error
1124
1125       else
1126          Error_Msg_N ("invalid procedure or entry call", N);
1127       end if;
1128    end Analyze_Procedure_Call;
1129
1130    ------------------------------
1131    -- Analyze_Return_Statement --
1132    ------------------------------
1133
1134    procedure Analyze_Return_Statement (N : Node_Id) is
1135       Loc      : constant Source_Ptr := Sloc (N);
1136       Expr     : Node_Id;
1137       Scope_Id : Entity_Id;
1138       Kind     : Entity_Kind;
1139       R_Type   : Entity_Id;
1140
1141       Stm_Entity : constant Entity_Id   :=
1142                      New_Internal_Entity
1143                        (E_Return_Statement, Current_Scope, Loc, 'R');
1144
1145    begin
1146       if Enable_New_Return_Processing then --  ???Temporary hack.
1147          Analyze_A_Return_Statement (N);
1148          return;
1149       end if;
1150
1151       --  Find subprogram or accept statement enclosing the return statement
1152
1153       Scope_Id := Empty;
1154       for J in reverse 0 .. Scope_Stack.Last loop
1155          Scope_Id := Scope_Stack.Table (J).Entity;
1156          exit when Ekind (Scope_Id) /= E_Block and then
1157                    Ekind (Scope_Id) /= E_Loop;
1158       end loop;
1159
1160       pragma Assert (Present (Scope_Id));
1161
1162       Set_Return_Statement_Entity (N, Stm_Entity);
1163       Set_Return_Applies_To (Stm_Entity, Scope_Id);
1164
1165       Kind := Ekind (Scope_Id);
1166       Expr := Expression (N);
1167
1168       if Kind /= E_Function
1169         and then Kind /= E_Generic_Function
1170         and then Kind /= E_Procedure
1171         and then Kind /= E_Generic_Procedure
1172         and then Kind /= E_Entry
1173         and then Kind /= E_Entry_Family
1174       then
1175          Error_Msg_N ("illegal context for return statement", N);
1176
1177       elsif Present (Expr) then
1178          if Kind = E_Function or else Kind = E_Generic_Function then
1179             Set_Return_Present (Scope_Id);
1180             R_Type := Etype (Scope_Id);
1181             Analyze_And_Resolve (Expr, R_Type);
1182
1183             --  Ada 2005 (AI-318-02): When the result type is an anonymous
1184             --  access type, apply an implicit conversion of the expression
1185             --  to that type to force appropriate static and run-time
1186             --  accessibility checks.
1187
1188             if Ada_Version >= Ada_05
1189               and then Ekind (R_Type) = E_Anonymous_Access_Type
1190             then
1191                Rewrite (Expr, Convert_To (R_Type, Relocate_Node (Expr)));
1192                Analyze_And_Resolve (Expr, R_Type);
1193             end if;
1194
1195             if (Is_Class_Wide_Type (Etype (Expr))
1196                  or else Is_Dynamically_Tagged (Expr))
1197               and then not Is_Class_Wide_Type (R_Type)
1198             then
1199                Error_Msg_N
1200                  ("dynamically tagged expression not allowed!", Expr);
1201             end if;
1202
1203             Apply_Constraint_Check (Expr, R_Type);
1204
1205             --  Ada 2005 (AI-318-02): Return-by-reference types have been
1206             --  removed and replaced by anonymous access results. This is
1207             --  an incompatibility with Ada 95. Not clear whether this
1208             --  should be enforced yet or perhaps controllable with a
1209             --  special switch. ???
1210
1211             --  if Ada_Version >= Ada_05
1212             --    and then Is_Limited_Type (R_Type)
1213             --    and then Nkind (Expr) /= N_Aggregate
1214             --    and then Nkind (Expr) /= N_Extension_Aggregate
1215             --    and then Nkind (Expr) /= N_Function_Call
1216             --  then
1217             --     Error_Msg_N
1218             --       ("(Ada 2005) illegal operand for limited return", N);
1219             --  end if;
1220
1221             --  ??? A real run-time accessibility check is needed in cases
1222             --  involving dereferences of access parameters. For now we just
1223             --  check the static cases.
1224
1225             if Is_Inherently_Limited_Type (Etype (Scope_Id))
1226               and then Object_Access_Level (Expr)
1227                 > Subprogram_Access_Level (Scope_Id)
1228             then
1229                Rewrite (N,
1230                  Make_Raise_Program_Error (Loc,
1231                    Reason => PE_Accessibility_Check_Failed));
1232                Analyze (N);
1233
1234                Error_Msg_N
1235                  ("cannot return a local value by reference?", N);
1236                Error_Msg_NE
1237                  ("\& will be raised at run time?",
1238                   N, Standard_Program_Error);
1239             end if;
1240
1241          elsif Kind = E_Procedure or else Kind = E_Generic_Procedure then
1242             Error_Msg_N ("procedure cannot return value (use function)", N);
1243
1244          else
1245             Error_Msg_N ("accept statement cannot return value", N);
1246          end if;
1247
1248       --  No expression present
1249
1250       else
1251          if Kind = E_Function or Kind = E_Generic_Function then
1252             Error_Msg_N ("missing expression in return from function", N);
1253          end if;
1254
1255          if (Ekind (Scope_Id) = E_Procedure
1256               or else Ekind (Scope_Id) = E_Generic_Procedure)
1257            and then No_Return (Scope_Id)
1258          then
1259             Error_Msg_N
1260               ("RETURN statement not allowed (No_Return)", N);
1261          end if;
1262       end if;
1263
1264       Check_Unreachable_Code (N);
1265    end Analyze_Return_Statement;
1266
1267    -------------------------
1268    -- Analyze_Return_Type --
1269    -------------------------
1270
1271    procedure Analyze_Return_Type (N : Node_Id) is
1272       Designator : constant Entity_Id := Defining_Entity (N);
1273       Typ        : Entity_Id := Empty;
1274
1275    begin
1276       --  Normal case where result definition does not indicate an error
1277
1278       if Result_Definition (N) /= Error then
1279          if Nkind (Result_Definition (N)) = N_Access_Definition then
1280             Typ := Access_Definition (N, Result_Definition (N));
1281             Set_Parent (Typ, Result_Definition (N));
1282             Set_Is_Local_Anonymous_Access (Typ);
1283             Set_Etype (Designator, Typ);
1284
1285          --  Subtype_Mark case
1286
1287          else
1288             Find_Type (Result_Definition (N));
1289             Typ := Entity (Result_Definition (N));
1290             Set_Etype (Designator, Typ);
1291
1292             if Ekind (Typ) = E_Incomplete_Type
1293               and then Is_Value_Type (Typ)
1294             then
1295                null;
1296
1297             elsif Ekind (Typ) = E_Incomplete_Type
1298               or else (Is_Class_Wide_Type (Typ)
1299                          and then
1300                            Ekind (Root_Type (Typ)) = E_Incomplete_Type)
1301             then
1302                Error_Msg_N
1303                  ("invalid use of incomplete type", Result_Definition (N));
1304             end if;
1305          end if;
1306
1307          --  Ada 2005 (AI-231): Ensure proper usage of null exclusion
1308
1309          Null_Exclusion_Static_Checks (N);
1310
1311       --  Case where result definition does indicate an error
1312
1313       else
1314          Set_Etype (Designator, Any_Type);
1315       end if;
1316    end Analyze_Return_Type;
1317
1318    -----------------------------
1319    -- Analyze_Subprogram_Body --
1320    -----------------------------
1321
1322    --  This procedure is called for regular subprogram bodies, generic bodies,
1323    --  and for subprogram stubs of both kinds. In the case of stubs, only the
1324    --  specification matters, and is used to create a proper declaration for
1325    --  the subprogram, or to perform conformance checks.
1326
1327    procedure Analyze_Subprogram_Body (N : Node_Id) is
1328       Loc          : constant Source_Ptr := Sloc (N);
1329       Body_Spec    : constant Node_Id    := Specification (N);
1330       Body_Id      : Entity_Id           := Defining_Entity (Body_Spec);
1331       Prev_Id      : constant Entity_Id  := Current_Entity_In_Scope (Body_Id);
1332       Body_Deleted : constant Boolean    := False;
1333
1334       HSS          : Node_Id;
1335       Spec_Id      : Entity_Id;
1336       Spec_Decl    : Node_Id   := Empty;
1337       Last_Formal  : Entity_Id := Empty;
1338       Conformant   : Boolean;
1339       Missing_Ret  : Boolean;
1340       P_Ent        : Entity_Id;
1341
1342       procedure Check_Anonymous_Return;
1343       --  (Ada 2005): if a function returns an access type that denotes a task,
1344       --  or a type that contains tasks, we must create a master entity for
1345       --  the anonymous type, which typically will be used in an allocator
1346       --  in the body of the function.
1347
1348       procedure Check_Inline_Pragma (Spec : in out Node_Id);
1349       --  Look ahead to recognize a pragma that may appear after the body.
1350       --  If there is a previous spec, check that it appears in the same
1351       --  declarative part. If the pragma is Inline_Always, perform inlining
1352       --  unconditionally, otherwise only if Front_End_Inlining is requested.
1353       --  If the body acts as a spec, and inlining is required, we create a
1354       --  subprogram declaration for it, in order to attach the body to inline.
1355
1356       procedure Copy_Parameter_List (Plist : List_Id);
1357       --  Utility to create a parameter profile for a new subprogram spec,
1358       --  when the subprogram has a body that acts as spec. This is done for
1359       --  some cases of inlining, and for private protected ops.
1360
1361       procedure Verify_Overriding_Indicator;
1362       --  If there was a previous spec, the entity has been entered in the
1363       --  current scope previously. If the body itself carries an overriding
1364       --  indicator, check that it is consistent with the known status of the
1365       --  entity.
1366
1367       ----------------------------
1368       -- Check_Anonymous_Return --
1369       ----------------------------
1370
1371       procedure Check_Anonymous_Return is
1372          Decl : Node_Id;
1373          Scop : Entity_Id;
1374
1375       begin
1376          if Present (Spec_Id) then
1377             Scop := Spec_Id;
1378          else
1379             Scop := Body_Id;
1380          end if;
1381
1382          if Ekind (Scop) = E_Function
1383            and then Ekind (Etype (Scop)) = E_Anonymous_Access_Type
1384            and then Has_Task (Designated_Type (Etype (Scop)))
1385            and then Expander_Active
1386          then
1387             Decl :=
1388               Make_Object_Declaration (Loc,
1389                 Defining_Identifier =>
1390                   Make_Defining_Identifier (Loc, Name_uMaster),
1391                 Constant_Present => True,
1392                 Object_Definition =>
1393                   New_Reference_To (RTE (RE_Master_Id), Loc),
1394                 Expression =>
1395                   Make_Explicit_Dereference (Loc,
1396                     New_Reference_To (RTE (RE_Current_Master), Loc)));
1397
1398             if Present (Declarations (N)) then
1399                Prepend (Decl, Declarations (N));
1400             else
1401                Set_Declarations (N, New_List (Decl));
1402             end if;
1403
1404             Set_Master_Id (Etype (Scop), Defining_Identifier (Decl));
1405             Set_Has_Master_Entity (Scop);
1406          end if;
1407       end Check_Anonymous_Return;
1408
1409       -------------------------
1410       -- Check_Inline_Pragma --
1411       -------------------------
1412
1413       procedure Check_Inline_Pragma (Spec : in out Node_Id) is
1414          Prag  : Node_Id;
1415          Plist : List_Id;
1416
1417       begin
1418          if not Expander_Active then
1419             return;
1420          end if;
1421
1422          if Is_List_Member (N)
1423            and then Present (Next (N))
1424            and then Nkind (Next (N)) = N_Pragma
1425          then
1426             Prag := Next (N);
1427
1428             if Nkind (Prag) = N_Pragma
1429               and then
1430                  (Get_Pragma_Id (Chars (Prag)) = Pragma_Inline_Always
1431                   or else
1432                     (Front_End_Inlining
1433                      and then Get_Pragma_Id (Chars (Prag)) = Pragma_Inline))
1434               and then
1435                  Chars
1436                    (Expression (First (Pragma_Argument_Associations (Prag))))
1437                       = Chars (Body_Id)
1438             then
1439                Prag := Next (N);
1440             else
1441                Prag := Empty;
1442             end if;
1443          else
1444             Prag := Empty;
1445          end if;
1446
1447          if Present (Prag) then
1448             if Present (Spec_Id) then
1449                if List_Containing (N) =
1450                  List_Containing (Unit_Declaration_Node (Spec_Id))
1451                then
1452                   Analyze (Prag);
1453                end if;
1454
1455             else
1456                --  Create a subprogram declaration, to make treatment uniform
1457
1458                declare
1459                   Subp : constant Entity_Id :=
1460                     Make_Defining_Identifier (Loc, Chars (Body_Id));
1461                   Decl : constant Node_Id :=
1462                     Make_Subprogram_Declaration (Loc,
1463                       Specification =>  New_Copy_Tree (Specification (N)));
1464                begin
1465                   Set_Defining_Unit_Name (Specification (Decl), Subp);
1466
1467                   if Present (First_Formal (Body_Id)) then
1468                      Plist := New_List;
1469                      Copy_Parameter_List (Plist);
1470                      Set_Parameter_Specifications
1471                        (Specification (Decl), Plist);
1472                   end if;
1473
1474                   Insert_Before (N, Decl);
1475                   Analyze (Decl);
1476                   Analyze (Prag);
1477                   Set_Has_Pragma_Inline (Subp);
1478
1479                   if Get_Pragma_Id (Chars (Prag)) = Pragma_Inline_Always then
1480                      Set_Is_Inlined (Subp);
1481                      Set_Next_Rep_Item (Prag, First_Rep_Item (Subp));
1482                      Set_First_Rep_Item (Subp, Prag);
1483                   end if;
1484
1485                   Spec := Subp;
1486                end;
1487             end if;
1488          end if;
1489       end Check_Inline_Pragma;
1490
1491       -------------------------
1492       -- Copy_Parameter_List --
1493       -------------------------
1494
1495       procedure Copy_Parameter_List (Plist : List_Id) is
1496          Formal : Entity_Id;
1497
1498       begin
1499          Formal := First_Formal (Body_Id);
1500
1501          while Present (Formal) loop
1502             Append
1503               (Make_Parameter_Specification (Loc,
1504                 Defining_Identifier =>
1505                   Make_Defining_Identifier (Sloc (Formal),
1506                     Chars => Chars (Formal)),
1507                 In_Present  => In_Present (Parent (Formal)),
1508                 Out_Present => Out_Present (Parent (Formal)),
1509              Parameter_Type =>
1510                   New_Reference_To (Etype (Formal), Loc),
1511                 Expression =>
1512                   New_Copy_Tree (Expression (Parent (Formal)))),
1513               Plist);
1514
1515             Next_Formal (Formal);
1516          end loop;
1517       end Copy_Parameter_List;
1518
1519       ---------------------------------
1520       -- Verify_Overriding_Indicator --
1521       ---------------------------------
1522
1523       procedure Verify_Overriding_Indicator is
1524       begin
1525          if Must_Override (Body_Spec)
1526            and then not Is_Overriding_Operation (Spec_Id)
1527          then
1528             Error_Msg_NE
1529               ("subprogram& is not overriding", Body_Spec, Spec_Id);
1530
1531          elsif Must_Not_Override (Body_Spec)
1532               and then Is_Overriding_Operation (Spec_Id)
1533          then
1534             Error_Msg_NE
1535               ("subprogram& overrides inherited operation",
1536                  Body_Spec, Spec_Id);
1537          end if;
1538       end Verify_Overriding_Indicator;
1539
1540    --  Start of processing for Analyze_Subprogram_Body
1541
1542    begin
1543       if Debug_Flag_C then
1544          Write_Str ("====  Compiling subprogram body ");
1545          Write_Name (Chars (Body_Id));
1546          Write_Str (" from ");
1547          Write_Location (Loc);
1548          Write_Eol;
1549       end if;
1550
1551       Trace_Scope (N, Body_Id, " Analyze subprogram");
1552
1553       --  Generic subprograms are handled separately. They always have a
1554       --  generic specification. Determine whether current scope has a
1555       --  previous declaration.
1556
1557       --  If the subprogram body is defined within an instance of the same
1558       --  name, the instance appears as a package renaming, and will be hidden
1559       --  within the subprogram.
1560
1561       if Present (Prev_Id)
1562         and then not Is_Overloadable (Prev_Id)
1563         and then (Nkind (Parent (Prev_Id)) /= N_Package_Renaming_Declaration
1564                    or else Comes_From_Source (Prev_Id))
1565       then
1566          if Is_Generic_Subprogram (Prev_Id) then
1567             Spec_Id := Prev_Id;
1568             Set_Is_Compilation_Unit (Body_Id, Is_Compilation_Unit (Spec_Id));
1569             Set_Is_Child_Unit       (Body_Id, Is_Child_Unit       (Spec_Id));
1570
1571             Analyze_Generic_Subprogram_Body (N, Spec_Id);
1572             return;
1573
1574          else
1575             --  Previous entity conflicts with subprogram name. Attempting to
1576             --  enter name will post error.
1577
1578             Enter_Name (Body_Id);
1579             return;
1580          end if;
1581
1582       --  Non-generic case, find the subprogram declaration, if one was seen,
1583       --  or enter new overloaded entity in the current scope. If the
1584       --  Current_Entity is the Body_Id itself, the unit is being analyzed as
1585       --  part of the context of one of its subunits. No need to redo the
1586       --  analysis.
1587
1588       elsif Prev_Id = Body_Id
1589         and then Has_Completion (Body_Id)
1590       then
1591          return;
1592
1593       else
1594          Body_Id := Analyze_Subprogram_Specification (Body_Spec);
1595
1596          if Nkind (N) = N_Subprogram_Body_Stub
1597            or else No (Corresponding_Spec (N))
1598          then
1599             Spec_Id := Find_Corresponding_Spec (N);
1600
1601             --  If this is a duplicate body, no point in analyzing it
1602
1603             if Error_Posted (N) then
1604                return;
1605             end if;
1606
1607             --  A subprogram body should cause freezing of its own declaration,
1608             --  but if there was no previous explicit declaration, then the
1609             --  subprogram will get frozen too late (there may be code within
1610             --  the body that depends on the subprogram having been frozen,
1611             --  such as uses of extra formals), so we force it to be frozen
1612             --  here. Same holds if the body and the spec are compilation
1613             --  units.
1614
1615             if No (Spec_Id) then
1616                Freeze_Before (N, Body_Id);
1617
1618             elsif Nkind (Parent (N)) = N_Compilation_Unit then
1619                Freeze_Before (N, Spec_Id);
1620             end if;
1621          else
1622             Spec_Id := Corresponding_Spec (N);
1623          end if;
1624       end if;
1625
1626       --  Do not inline any subprogram that contains nested subprograms, since
1627       --  the backend inlining circuit seems to generate uninitialized
1628       --  references in this case. We know this happens in the case of front
1629       --  end ZCX support, but it also appears it can happen in other cases as
1630       --  well. The backend often rejects attempts to inline in the case of
1631       --  nested procedures anyway, so little if anything is lost by this.
1632       --  Note that this is test is for the benefit of the back-end. There is
1633       --  a separate test for front-end inlining that also rejects nested
1634       --  subprograms.
1635
1636       --  Do not do this test if errors have been detected, because in some
1637       --  error cases, this code blows up, and we don't need it anyway if
1638       --  there have been errors, since we won't get to the linker anyway.
1639
1640       if Comes_From_Source (Body_Id)
1641         and then Serious_Errors_Detected = 0
1642       then
1643          P_Ent := Body_Id;
1644          loop
1645             P_Ent := Scope (P_Ent);
1646             exit when No (P_Ent) or else P_Ent = Standard_Standard;
1647
1648             if Is_Subprogram (P_Ent) then
1649                Set_Is_Inlined (P_Ent, False);
1650
1651                if Comes_From_Source (P_Ent)
1652                  and then Has_Pragma_Inline (P_Ent)
1653                then
1654                   Cannot_Inline
1655                     ("cannot inline& (nested subprogram)?",
1656                      N, P_Ent);
1657                end if;
1658             end if;
1659          end loop;
1660       end if;
1661
1662       Check_Inline_Pragma (Spec_Id);
1663
1664       --  Case of fully private operation in the body of the protected type.
1665       --  We must create a declaration for the subprogram, in order to attach
1666       --  the protected subprogram that will be used in internal calls.
1667
1668       if No (Spec_Id)
1669         and then Comes_From_Source (N)
1670         and then Is_Protected_Type (Current_Scope)
1671       then
1672          declare
1673             Decl     : Node_Id;
1674             Plist    : List_Id;
1675             Formal   : Entity_Id;
1676             New_Spec : Node_Id;
1677
1678          begin
1679             Formal := First_Formal (Body_Id);
1680
1681             --  The protected operation always has at least one formal, namely
1682             --  the object itself, but it is only placed in the parameter list
1683             --  if expansion is enabled.
1684
1685             if Present (Formal)
1686               or else Expander_Active
1687             then
1688                Plist := New_List;
1689
1690             else
1691                Plist := No_List;
1692             end if;
1693
1694             Copy_Parameter_List (Plist);
1695
1696             if Nkind (Body_Spec) = N_Procedure_Specification then
1697                New_Spec :=
1698                  Make_Procedure_Specification (Loc,
1699                     Defining_Unit_Name =>
1700                       Make_Defining_Identifier (Sloc (Body_Id),
1701                         Chars => Chars (Body_Id)),
1702                     Parameter_Specifications => Plist);
1703             else
1704                New_Spec :=
1705                  Make_Function_Specification (Loc,
1706                     Defining_Unit_Name =>
1707                       Make_Defining_Identifier (Sloc (Body_Id),
1708                         Chars => Chars (Body_Id)),
1709                     Parameter_Specifications => Plist,
1710                     Result_Definition =>
1711                       New_Occurrence_Of (Etype (Body_Id), Loc));
1712             end if;
1713
1714             Decl :=
1715               Make_Subprogram_Declaration (Loc,
1716                 Specification => New_Spec);
1717             Insert_Before (N, Decl);
1718             Spec_Id := Defining_Unit_Name (New_Spec);
1719
1720             --  Indicate that the entity comes from source, to ensure that
1721             --  cross-reference information is properly generated. The body
1722             --  itself is rewritten during expansion, and the body entity will
1723             --  not appear in calls to the operation.
1724
1725             Set_Comes_From_Source (Spec_Id, True);
1726             Analyze (Decl);
1727             Set_Has_Completion (Spec_Id);
1728             Set_Convention (Spec_Id, Convention_Protected);
1729          end;
1730
1731       elsif Present (Spec_Id) then
1732          Spec_Decl := Unit_Declaration_Node (Spec_Id);
1733          Verify_Overriding_Indicator;
1734       end if;
1735
1736       --  Place subprogram on scope stack, and make formals visible. If there
1737       --  is a spec, the visible entity remains that of the spec.
1738
1739       if Present (Spec_Id) then
1740          Generate_Reference (Spec_Id, Body_Id, 'b', Set_Ref => False);
1741
1742          if Is_Child_Unit (Spec_Id) then
1743             Generate_Reference (Spec_Id, Scope (Spec_Id), 'k', False);
1744          end if;
1745
1746          if Style_Check then
1747             Style.Check_Identifier (Body_Id, Spec_Id);
1748          end if;
1749
1750          Set_Is_Compilation_Unit (Body_Id, Is_Compilation_Unit (Spec_Id));
1751          Set_Is_Child_Unit       (Body_Id, Is_Child_Unit       (Spec_Id));
1752
1753          if Is_Abstract_Subprogram (Spec_Id) then
1754             Error_Msg_N ("an abstract subprogram cannot have a body", N);
1755             return;
1756          else
1757             Set_Convention (Body_Id, Convention (Spec_Id));
1758             Set_Has_Completion (Spec_Id);
1759
1760             if Is_Protected_Type (Scope (Spec_Id)) then
1761                Set_Privals_Chain (Spec_Id, New_Elmt_List);
1762             end if;
1763
1764             --  If this is a body generated for a renaming, do not check for
1765             --  full conformance. The check is redundant, because the spec of
1766             --  the body is a copy of the spec in the renaming declaration,
1767             --  and the test can lead to spurious errors on nested defaults.
1768
1769             if Present (Spec_Decl)
1770               and then not Comes_From_Source (N)
1771               and then
1772                 (Nkind (Original_Node (Spec_Decl)) =
1773                                         N_Subprogram_Renaming_Declaration
1774                    or else (Present (Corresponding_Body (Spec_Decl))
1775                               and then
1776                                 Nkind (Unit_Declaration_Node
1777                                         (Corresponding_Body (Spec_Decl))) =
1778                                            N_Subprogram_Renaming_Declaration))
1779             then
1780                Conformant := True;
1781             else
1782                Check_Conformance
1783                  (Body_Id, Spec_Id,
1784                    Fully_Conformant, True, Conformant, Body_Id);
1785             end if;
1786
1787             --  If the body is not fully conformant, we have to decide if we
1788             --  should analyze it or not. If it has a really messed up profile
1789             --  then we probably should not analyze it, since we will get too
1790             --  many bogus messages.
1791
1792             --  Our decision is to go ahead in the non-fully conformant case
1793             --  only if it is at least mode conformant with the spec. Note
1794             --  that the call to Check_Fully_Conformant has issued the proper
1795             --  error messages to complain about the lack of conformance.
1796
1797             if not Conformant
1798               and then not Mode_Conformant (Body_Id, Spec_Id)
1799             then
1800                return;
1801             end if;
1802          end if;
1803
1804          if Spec_Id /= Body_Id then
1805             Reference_Body_Formals (Spec_Id, Body_Id);
1806          end if;
1807
1808          if Nkind (N) /= N_Subprogram_Body_Stub then
1809             Set_Corresponding_Spec (N, Spec_Id);
1810
1811             --  Ada 2005 (AI-345): Restore the correct Etype: here we undo the
1812             --  work done by Analyze_Subprogram_Specification to allow the
1813             --  overriding of task, protected and interface primitives.
1814
1815             if Comes_From_Source (Spec_Id)
1816               and then Present (First_Entity (Spec_Id))
1817               and then Ekind (Etype (First_Entity (Spec_Id))) = E_Record_Type
1818               and then Is_Tagged_Type (Etype (First_Entity (Spec_Id)))
1819               and then Present (Abstract_Interfaces
1820                                 (Etype (First_Entity (Spec_Id))))
1821               and then Present (Corresponding_Concurrent_Type
1822                                 (Etype (First_Entity (Spec_Id))))
1823             then
1824                Set_Etype (First_Entity (Spec_Id),
1825                  Corresponding_Concurrent_Type
1826                    (Etype (First_Entity (Spec_Id))));
1827             end if;
1828
1829             --  Now make the formals visible, and place subprogram
1830             --  on scope stack.
1831
1832             Install_Formals (Spec_Id);
1833             Last_Formal := Last_Entity (Spec_Id);
1834             Push_Scope (Spec_Id);
1835
1836             --  Make sure that the subprogram is immediately visible. For
1837             --  child units that have no separate spec this is indispensable.
1838             --  Otherwise it is safe albeit redundant.
1839
1840             Set_Is_Immediately_Visible (Spec_Id);
1841          end if;
1842
1843          Set_Corresponding_Body (Unit_Declaration_Node (Spec_Id), Body_Id);
1844          Set_Ekind (Body_Id, E_Subprogram_Body);
1845          Set_Scope (Body_Id, Scope (Spec_Id));
1846          Set_Is_Obsolescent (Body_Id, Is_Obsolescent (Spec_Id));
1847
1848       --  Case of subprogram body with no previous spec
1849
1850       else
1851          if Style_Check
1852            and then Comes_From_Source (Body_Id)
1853            and then not Suppress_Style_Checks (Body_Id)
1854            and then not In_Instance
1855          then
1856             Style.Body_With_No_Spec (N);
1857          end if;
1858
1859          New_Overloaded_Entity (Body_Id);
1860
1861          if Nkind (N) /= N_Subprogram_Body_Stub then
1862             Set_Acts_As_Spec (N);
1863             Generate_Definition (Body_Id);
1864             Generate_Reference
1865               (Body_Id, Body_Id, 'b', Set_Ref => False, Force => True);
1866             Generate_Reference_To_Formals (Body_Id);
1867             Install_Formals (Body_Id);
1868             Push_Scope (Body_Id);
1869          end if;
1870       end if;
1871
1872       --  Ada 2005 (AI-251): Check wrong placement of abstract interface
1873       --  primitives, and update anonymous access returns with limited views.
1874
1875       if Ada_Version >= Ada_05
1876         and then Comes_From_Source (N)
1877       then
1878          declare
1879             E    : Entity_Id;
1880             Etyp : Entity_Id;
1881             Rtyp : Entity_Id;
1882
1883          begin
1884             --  Check the type of the formals
1885
1886             E := First_Entity (Body_Id);
1887             while Present (E) loop
1888                Etyp := Etype (E);
1889
1890                if Is_Access_Type (Etyp) then
1891                   Etyp := Directly_Designated_Type (Etyp);
1892                end if;
1893
1894                if not Is_Class_Wide_Type (Etyp)
1895                  and then Is_Interface (Etyp)
1896                then
1897                   Error_Msg_Name_1 := Chars (Defining_Entity (N));
1898                   Error_Msg_N
1899                     ("(Ada 2005) abstract interface primitives must be" &
1900                      " defined in package specs", N);
1901                   exit;
1902                end if;
1903
1904                Next_Entity (E);
1905             end loop;
1906
1907             --  In case of functions, check the type of the result
1908
1909             if Ekind (Body_Id) = E_Function then
1910                Etyp := Etype (Body_Id);
1911
1912                if Is_Access_Type (Etyp) then
1913                   Etyp := Directly_Designated_Type (Etyp);
1914                end if;
1915
1916                if not Is_Class_Wide_Type (Etyp)
1917                  and then Is_Interface (Etyp)
1918                then
1919                   Error_Msg_Name_1 := Chars (Defining_Entity (N));
1920                   Error_Msg_N
1921                     ("(Ada 2005) abstract interface primitives must be" &
1922                      " defined in package specs", N);
1923                end if;
1924             end if;
1925
1926             --  If the return type is an anonymous access type whose
1927             --  designated type is the limited view of a class-wide type
1928             --  and the non-limited view is available. update the return
1929             --  type accordingly.
1930
1931             Rtyp := Etype (Current_Scope);
1932
1933             if Ekind (Rtyp) = E_Anonymous_Access_Type then
1934                Etyp := Directly_Designated_Type (Rtyp);
1935
1936                if Is_Class_Wide_Type (Etyp)
1937                  and then From_With_Type (Etyp)
1938                then
1939                   Set_Directly_Designated_Type
1940                     (Etype (Current_Scope), Available_View (Etyp));
1941                end if;
1942             end if;
1943          end;
1944       end if;
1945
1946       --  If this is the proper body of a stub, we must verify that the stub
1947       --  conforms to the body, and to the previous spec if one was present.
1948       --  we know already that the body conforms to that spec. This test is
1949       --  only required for subprograms that come from source.
1950
1951       if Nkind (Parent (N)) = N_Subunit
1952         and then Comes_From_Source (N)
1953         and then not Error_Posted (Body_Id)
1954         and then Nkind (Corresponding_Stub (Parent (N))) =
1955                                                 N_Subprogram_Body_Stub
1956       then
1957          declare
1958             Old_Id : constant Entity_Id :=
1959                        Defining_Entity
1960                          (Specification (Corresponding_Stub (Parent (N))));
1961
1962             Conformant : Boolean := False;
1963
1964          begin
1965             if No (Spec_Id) then
1966                Check_Fully_Conformant (Body_Id, Old_Id);
1967
1968             else
1969                Check_Conformance
1970                  (Body_Id, Old_Id, Fully_Conformant, False, Conformant);
1971
1972                if not Conformant then
1973
1974                   --  The stub was taken to be a new declaration. Indicate
1975                   --  that it lacks a body.
1976
1977                   Set_Has_Completion (Old_Id, False);
1978                end if;
1979             end if;
1980          end;
1981       end if;
1982
1983       Set_Has_Completion (Body_Id);
1984       Check_Eliminated (Body_Id);
1985
1986       if Nkind (N) = N_Subprogram_Body_Stub then
1987          return;
1988
1989       elsif Present (Spec_Id)
1990         and then Expander_Active
1991         and then
1992           (Is_Always_Inlined (Spec_Id)
1993              or else (Has_Pragma_Inline (Spec_Id) and Front_End_Inlining))
1994       then
1995          Build_Body_To_Inline (N, Spec_Id);
1996       end if;
1997
1998       --  Ada 2005 (AI-262): In library subprogram bodies, after the analysis
1999       --  if its specification we have to install the private withed units.
2000
2001       if Is_Compilation_Unit (Body_Id)
2002         and then Scope (Body_Id) = Standard_Standard
2003       then
2004          Install_Private_With_Clauses (Body_Id);
2005       end if;
2006
2007       Check_Anonymous_Return;
2008
2009       --  Now we can go on to analyze the body
2010
2011       HSS := Handled_Statement_Sequence (N);
2012       Set_Actual_Subtypes (N, Current_Scope);
2013       Analyze_Declarations (Declarations (N));
2014       Check_Completion;
2015       Analyze (HSS);
2016       Process_End_Label (HSS, 't', Current_Scope);
2017       End_Scope;
2018       Check_Subprogram_Order (N);
2019       Set_Analyzed (Body_Id);
2020
2021       --  If we have a separate spec, then the analysis of the declarations
2022       --  caused the entities in the body to be chained to the spec id, but
2023       --  we want them chained to the body id. Only the formal parameters
2024       --  end up chained to the spec id in this case.
2025
2026       if Present (Spec_Id) then
2027
2028          --  We must conform to the categorization of our spec
2029
2030          Validate_Categorization_Dependency (N, Spec_Id);
2031
2032          --  And if this is a child unit, the parent units must conform
2033
2034          if Is_Child_Unit (Spec_Id) then
2035             Validate_Categorization_Dependency
2036               (Unit_Declaration_Node (Spec_Id), Spec_Id);
2037          end if;
2038
2039          if Present (Last_Formal) then
2040             Set_Next_Entity
2041               (Last_Entity (Body_Id), Next_Entity (Last_Formal));
2042             Set_Next_Entity (Last_Formal, Empty);
2043             Set_Last_Entity (Body_Id, Last_Entity (Spec_Id));
2044             Set_Last_Entity (Spec_Id, Last_Formal);
2045
2046          else
2047             Set_First_Entity (Body_Id, First_Entity (Spec_Id));
2048             Set_Last_Entity  (Body_Id, Last_Entity (Spec_Id));
2049             Set_First_Entity (Spec_Id, Empty);
2050             Set_Last_Entity  (Spec_Id, Empty);
2051          end if;
2052       end if;
2053
2054       --  If function, check return statements
2055
2056       if Nkind (Body_Spec) = N_Function_Specification then
2057          declare
2058             Id : Entity_Id;
2059
2060          begin
2061             if Present (Spec_Id) then
2062                Id := Spec_Id;
2063             else
2064                Id := Body_Id;
2065             end if;
2066
2067             if Return_Present (Id) then
2068                Check_Returns (HSS, 'F', Missing_Ret);
2069
2070                if Missing_Ret then
2071                   Set_Has_Missing_Return (Id);
2072                end if;
2073
2074             elsif not Is_Machine_Code_Subprogram (Id)
2075               and then not Body_Deleted
2076             then
2077                Error_Msg_N ("missing RETURN statement in function body", N);
2078             end if;
2079          end;
2080
2081       --  If procedure with No_Return, check returns
2082
2083       elsif Nkind (Body_Spec) = N_Procedure_Specification
2084         and then Present (Spec_Id)
2085         and then No_Return (Spec_Id)
2086       then
2087          Check_Returns (HSS, 'P', Missing_Ret, Spec_Id);
2088       end if;
2089
2090       --  Now we are going to check for variables that are never modified in
2091       --  the body of the procedure. We omit these checks if the first
2092       --  statement of the procedure raises an exception. In particular this
2093       --  deals with the common idiom of a stubbed function, which might
2094       --  appear as something like
2095
2096       --     function F (A : Integer) return Some_Type;
2097       --        X : Some_Type;
2098       --     begin
2099       --        raise Program_Error;
2100       --        return X;
2101       --     end F;
2102
2103       --  Here the purpose of X is simply to satisfy the (annoying)
2104       --  requirement in Ada that there be at least one return, and we
2105       --  certainly do not want to go posting warnings on X that it is not
2106       --  initialized!
2107
2108       declare
2109          Stm : Node_Id := First (Statements (HSS));
2110
2111       begin
2112          --  Skip initial labels (for one thing this occurs when we are in
2113          --  front end ZCX mode, but in any case it is irrelevant), and also
2114          --  initial Push_xxx_Error_Label nodes, which are also irrelevant.
2115
2116          while Nkind (Stm) = N_Label
2117            or else Nkind (Stm) in N_Push_xxx_Label
2118          loop
2119             Next (Stm);
2120          end loop;
2121
2122          --  Do the test on the original statement before expansion
2123
2124          declare
2125             Ostm : constant Node_Id := Original_Node (Stm);
2126
2127          begin
2128             --  If explicit raise statement, return with no checks
2129
2130             if Nkind (Ostm) = N_Raise_Statement then
2131                return;
2132
2133             --  Check for explicit call cases which likely raise an exception
2134
2135             elsif Nkind (Ostm) = N_Procedure_Call_Statement then
2136                if Is_Entity_Name (Name (Ostm)) then
2137                   declare
2138                      Ent : constant Entity_Id := Entity (Name (Ostm));
2139
2140                   begin
2141                      --  If the procedure is marked No_Return, then likely it
2142                      --  raises an exception, but in any case it is not coming
2143                      --  back here, so no need to check beyond the call.
2144
2145                      if Ekind (Ent) = E_Procedure
2146                        and then No_Return (Ent)
2147                      then
2148                         return;
2149
2150                      --  If the procedure name is Raise_Exception, then also
2151                      --  assume that it raises an exception. The main target
2152                      --  here is Ada.Exceptions.Raise_Exception, but this name
2153                      --  is pretty evocative in any context! Note that the
2154                      --  procedure in Ada.Exceptions is not marked No_Return
2155                      --  because of the annoying case of the null exception Id.
2156
2157                      elsif Chars (Ent) = Name_Raise_Exception then
2158                         return;
2159                      end if;
2160                   end;
2161                end if;
2162             end if;
2163          end;
2164       end;
2165
2166       --  Check for variables that are never modified
2167
2168       declare
2169          E1, E2 : Entity_Id;
2170
2171       begin
2172          --  If there is a separate spec, then transfer Never_Set_In_Source
2173          --  flags from out parameters to the corresponding entities in the
2174          --  body. The reason we do that is we want to post error flags on
2175          --  the body entities, not the spec entities.
2176
2177          if Present (Spec_Id) then
2178             E1 := First_Entity (Spec_Id);
2179             while Present (E1) loop
2180                if Ekind (E1) = E_Out_Parameter then
2181                   E2 := First_Entity (Body_Id);
2182                   while Present (E2) loop
2183                      exit when Chars (E1) = Chars (E2);
2184                      Next_Entity (E2);
2185                   end loop;
2186
2187                   if Present (E2) then
2188                      Set_Never_Set_In_Source (E2, Never_Set_In_Source (E1));
2189                   end if;
2190                end if;
2191
2192                Next_Entity (E1);
2193             end loop;
2194          end if;
2195
2196          --  Check references in body unless it was deleted. Note that the
2197          --  check of Body_Deleted here is not just for efficiency, it is
2198          --  necessary to avoid junk warnings on formal parameters.
2199
2200          if not Body_Deleted then
2201             Check_References (Body_Id);
2202          end if;
2203       end;
2204    end Analyze_Subprogram_Body;
2205
2206    ------------------------------------
2207    -- Analyze_Subprogram_Declaration --
2208    ------------------------------------
2209
2210    procedure Analyze_Subprogram_Declaration (N : Node_Id) is
2211       Designator : constant Entity_Id :=
2212                      Analyze_Subprogram_Specification (Specification (N));
2213       Scop       : constant Entity_Id := Current_Scope;
2214
2215    --  Start of processing for Analyze_Subprogram_Declaration
2216
2217    begin
2218       Generate_Definition (Designator);
2219
2220       --  Check for RCI unit subprogram declarations for illegal inlined
2221       --  subprograms and subprograms having access parameter or limited
2222       --  parameter without Read and Write attributes (RM E.2.3(12-13)).
2223
2224       Validate_RCI_Subprogram_Declaration (N);
2225
2226       Trace_Scope
2227         (N,
2228          Defining_Entity (N),
2229          " Analyze subprogram spec. ");
2230
2231       if Debug_Flag_C then
2232          Write_Str ("====  Compiling subprogram spec ");
2233          Write_Name (Chars (Designator));
2234          Write_Str (" from ");
2235          Write_Location (Sloc (N));
2236          Write_Eol;
2237       end if;
2238
2239       New_Overloaded_Entity (Designator);
2240       Check_Delayed_Subprogram (Designator);
2241
2242       --  Ada 2005 (AI-251): Abstract interface primitives must be abstract
2243       --  or null.
2244
2245       if Ada_Version >= Ada_05
2246         and then Comes_From_Source (N)
2247         and then Is_Dispatching_Operation (Designator)
2248       then
2249          declare
2250             E    : Entity_Id;
2251             Etyp : Entity_Id;
2252
2253          begin
2254             if Has_Controlling_Result (Designator) then
2255                Etyp := Etype (Designator);
2256
2257             else
2258                E := First_Entity (Designator);
2259                while Present (E)
2260                  and then Is_Formal (E)
2261                  and then not Is_Controlling_Formal (E)
2262                loop
2263                   Next_Entity (E);
2264                end loop;
2265
2266                Etyp := Etype (E);
2267             end if;
2268
2269             if Is_Access_Type (Etyp) then
2270                Etyp := Directly_Designated_Type (Etyp);
2271             end if;
2272
2273             if Is_Interface (Etyp)
2274               and then not Is_Abstract_Subprogram (Designator)
2275               and then not (Ekind (Designator) = E_Procedure
2276                               and then Null_Present (Specification (N)))
2277             then
2278                Error_Msg_Name_1 := Chars (Defining_Entity (N));
2279                Error_Msg_N
2280                  ("(Ada 2005) interface subprogram % must be abstract or null",
2281                   N);
2282             end if;
2283          end;
2284       end if;
2285
2286       --  What is the following code for, it used to be
2287
2288       --  ???   Set_Suppress_Elaboration_Checks
2289       --  ???     (Designator, Elaboration_Checks_Suppressed (Designator));
2290
2291       --  The following seems equivalent, but a bit dubious
2292
2293       if Elaboration_Checks_Suppressed (Designator) then
2294          Set_Kill_Elaboration_Checks (Designator);
2295       end if;
2296
2297       if Scop /= Standard_Standard
2298         and then not Is_Child_Unit (Designator)
2299       then
2300          Set_Categorization_From_Scope (Designator, Scop);
2301       else
2302          --  For a compilation unit, check for library-unit pragmas
2303
2304          Push_Scope (Designator);
2305          Set_Categorization_From_Pragmas (N);
2306          Validate_Categorization_Dependency (N, Designator);
2307          Pop_Scope;
2308       end if;
2309
2310       --  For a compilation unit, set body required. This flag will only be
2311       --  reset if a valid Import or Interface pragma is processed later on.
2312
2313       if Nkind (Parent (N)) = N_Compilation_Unit then
2314          Set_Body_Required (Parent (N), True);
2315
2316          if Ada_Version >= Ada_05
2317            and then Nkind (Specification (N)) = N_Procedure_Specification
2318            and then Null_Present (Specification (N))
2319          then
2320             Error_Msg_N
2321               ("null procedure cannot be declared at library level", N);
2322          end if;
2323       end if;
2324
2325       Generate_Reference_To_Formals (Designator);
2326       Check_Eliminated (Designator);
2327
2328       --  Ada 2005: if procedure is declared with "is null" qualifier,
2329       --  it requires no body.
2330
2331       if Nkind (Specification (N)) = N_Procedure_Specification
2332         and then Null_Present (Specification (N))
2333       then
2334          Set_Has_Completion (Designator);
2335          Set_Is_Inlined (Designator);
2336
2337          if Is_Protected_Type (Current_Scope) then
2338             Error_Msg_N
2339               ("protected operation cannot be a null procedure", N);
2340          end if;
2341       end if;
2342    end Analyze_Subprogram_Declaration;
2343
2344    --------------------------------------
2345    -- Analyze_Subprogram_Specification --
2346    --------------------------------------
2347
2348    --  Reminder: N here really is a subprogram specification (not a subprogram
2349    --  declaration). This procedure is called to analyze the specification in
2350    --  both subprogram bodies and subprogram declarations (specs).
2351
2352    function Analyze_Subprogram_Specification (N : Node_Id) return Entity_Id is
2353       Designator : constant Entity_Id := Defining_Entity (N);
2354       Formal     : Entity_Id;
2355       Formal_Typ : Entity_Id;
2356       Formals    : constant List_Id   := Parameter_Specifications (N);
2357
2358    --  Start of processing for Analyze_Subprogram_Specification
2359
2360    begin
2361       Generate_Definition (Designator);
2362
2363       if Nkind (N) = N_Function_Specification then
2364          Set_Ekind (Designator, E_Function);
2365          Set_Mechanism (Designator, Default_Mechanism);
2366
2367       else
2368          Set_Ekind (Designator, E_Procedure);
2369          Set_Etype (Designator, Standard_Void_Type);
2370       end if;
2371
2372       --  Introduce new scope for analysis of the formals and of the
2373       --  return type.
2374
2375       Set_Scope (Designator, Current_Scope);
2376
2377       if Present (Formals) then
2378          Push_Scope (Designator);
2379          Process_Formals (Formals, N);
2380
2381          --  Ada 2005 (AI-345): Allow the overriding of interface primitives
2382          --  by subprograms which belong to a concurrent type implementing an
2383          --  interface. Set the parameter type of each controlling formal to
2384          --  the corresponding record type.
2385
2386          if Ada_Version >= Ada_05 then
2387             Formal := First_Formal (Designator);
2388             while Present (Formal) loop
2389                Formal_Typ := Etype (Formal);
2390
2391                if (Ekind (Formal_Typ) = E_Protected_Type
2392                      or else Ekind (Formal_Typ) = E_Task_Type)
2393                  and then Present (Corresponding_Record_Type (Formal_Typ))
2394                  and then Present (Abstract_Interfaces
2395                                   (Corresponding_Record_Type (Formal_Typ)))
2396                then
2397                   Set_Etype (Formal,
2398                     Corresponding_Record_Type (Formal_Typ));
2399                end if;
2400
2401                Formal := Next_Formal (Formal);
2402             end loop;
2403          end if;
2404
2405          End_Scope;
2406
2407       elsif Nkind (N) = N_Function_Specification then
2408          Analyze_Return_Type (N);
2409       end if;
2410
2411       if Nkind (N) = N_Function_Specification then
2412          if Nkind (Designator) = N_Defining_Operator_Symbol then
2413             Valid_Operator_Definition (Designator);
2414          end if;
2415
2416          May_Need_Actuals (Designator);
2417
2418          --  Ada 2005 (AI-251): In case of primitives associated with abstract
2419          --  interface types the following error message will be reported later
2420          --  (see Analyze_Subprogram_Declaration).
2421
2422          if Is_Abstract_Type (Etype (Designator))
2423            and then not Is_Interface (Etype (Designator))
2424            and then Nkind (Parent (N))
2425                       /= N_Abstract_Subprogram_Declaration
2426            and then (Nkind (Parent (N)))
2427                       /= N_Formal_Abstract_Subprogram_Declaration
2428            and then (Nkind (Parent (N)) /= N_Subprogram_Renaming_Declaration
2429                       or else not Is_Entity_Name (Name (Parent (N)))
2430                       or else not Is_Abstract_Subprogram
2431                                     (Entity (Name (Parent (N)))))
2432          then
2433             Error_Msg_N
2434               ("function that returns abstract type must be abstract", N);
2435          end if;
2436       end if;
2437
2438       return Designator;
2439    end Analyze_Subprogram_Specification;
2440
2441    --------------------------
2442    -- Build_Body_To_Inline --
2443    --------------------------
2444
2445    procedure Build_Body_To_Inline (N : Node_Id; Subp : Entity_Id) is
2446       Decl            : constant Node_Id := Unit_Declaration_Node (Subp);
2447       Original_Body   : Node_Id;
2448       Body_To_Analyze : Node_Id;
2449       Max_Size        : constant := 10;
2450       Stat_Count      : Integer := 0;
2451
2452       function Has_Excluded_Declaration (Decls : List_Id) return Boolean;
2453       --  Check for declarations that make inlining not worthwhile
2454
2455       function Has_Excluded_Statement   (Stats : List_Id) return Boolean;
2456       --  Check for statements that make inlining not worthwhile: any tasking
2457       --  statement, nested at any level. Keep track of total number of
2458       --  elementary statements, as a measure of acceptable size.
2459
2460       function Has_Pending_Instantiation return Boolean;
2461       --  If some enclosing body contains instantiations that appear before the
2462       --  corresponding generic body, the enclosing body has a freeze node so
2463       --  that it can be elaborated after the generic itself. This might
2464       --  conflict with subsequent inlinings, so that it is unsafe to try to
2465       --  inline in such a case.
2466
2467       function Has_Single_Return return Boolean;
2468       --  In general we cannot inline functions that return unconstrained type.
2469       --  However, we can handle such functions if all return statements return
2470       --  a local variable that is the only declaration in the body of the
2471       --  function. In that case the call can be replaced by that local
2472       --  variable as is done for other inlined calls.
2473
2474       procedure Remove_Pragmas;
2475       --  A pragma Unreferenced that mentions a formal parameter has no meaning
2476       --  when the body is inlined and the formals are rewritten. Remove it
2477       --  from body to inline. The analysis of the non-inlined body will handle
2478       --  the pragma properly.
2479
2480       function Uses_Secondary_Stack (Bod : Node_Id) return Boolean;
2481       --  If the body of the subprogram includes a call that returns an
2482       --  unconstrained type, the secondary stack is involved, and it
2483       --  is not worth inlining.
2484
2485       ------------------------------
2486       -- Has_Excluded_Declaration --
2487       ------------------------------
2488
2489       function Has_Excluded_Declaration (Decls : List_Id) return Boolean is
2490          D : Node_Id;
2491
2492          function Is_Unchecked_Conversion (D : Node_Id) return Boolean;
2493          --  Nested subprograms make a given body ineligible for inlining, but
2494          --  we make an exception for instantiations of unchecked conversion.
2495          --  The body has not been analyzed yet, so check the name, and verify
2496          --  that the visible entity with that name is the predefined unit.
2497
2498          -----------------------------
2499          -- Is_Unchecked_Conversion --
2500          -----------------------------
2501
2502          function Is_Unchecked_Conversion (D : Node_Id) return Boolean is
2503             Id   : constant Node_Id := Name (D);
2504             Conv : Entity_Id;
2505
2506          begin
2507             if Nkind (Id) = N_Identifier
2508               and then Chars (Id) = Name_Unchecked_Conversion
2509             then
2510                Conv := Current_Entity (Id);
2511
2512             elsif (Nkind (Id) = N_Selected_Component
2513                     or else Nkind (Id) = N_Expanded_Name)
2514               and then Chars (Selector_Name (Id)) = Name_Unchecked_Conversion
2515             then
2516                Conv := Current_Entity (Selector_Name (Id));
2517
2518             else
2519                return False;
2520             end if;
2521
2522             return Present (Conv)
2523               and then Is_Predefined_File_Name
2524                          (Unit_File_Name (Get_Source_Unit (Conv)))
2525               and then Is_Intrinsic_Subprogram (Conv);
2526          end Is_Unchecked_Conversion;
2527
2528       --  Start of processing for Has_Excluded_Declaration
2529
2530       begin
2531          D := First (Decls);
2532
2533          while Present (D) loop
2534             if       (Nkind (D) = N_Function_Instantiation
2535                         and then not Is_Unchecked_Conversion (D))
2536               or else Nkind (D) = N_Protected_Type_Declaration
2537               or else Nkind (D) = N_Package_Declaration
2538               or else Nkind (D) = N_Package_Instantiation
2539               or else Nkind (D) = N_Subprogram_Body
2540               or else Nkind (D) = N_Procedure_Instantiation
2541               or else Nkind (D) = N_Task_Type_Declaration
2542             then
2543                Cannot_Inline
2544                  ("cannot inline & (non-allowed declaration)?", D, Subp);
2545                return True;
2546             end if;
2547
2548             Next (D);
2549          end loop;
2550
2551          return False;
2552       end Has_Excluded_Declaration;
2553
2554       ----------------------------
2555       -- Has_Excluded_Statement --
2556       ----------------------------
2557
2558       function Has_Excluded_Statement (Stats : List_Id) return Boolean is
2559          S : Node_Id;
2560          E : Node_Id;
2561
2562       begin
2563          S := First (Stats);
2564          while Present (S) loop
2565             Stat_Count := Stat_Count + 1;
2566
2567             if Nkind (S) = N_Abort_Statement
2568               or else Nkind (S) = N_Asynchronous_Select
2569               or else Nkind (S) = N_Conditional_Entry_Call
2570               or else Nkind (S) = N_Delay_Relative_Statement
2571               or else Nkind (S) = N_Delay_Until_Statement
2572               or else Nkind (S) = N_Selective_Accept
2573               or else Nkind (S) = N_Timed_Entry_Call
2574             then
2575                Cannot_Inline
2576                  ("cannot inline & (non-allowed statement)?", S, Subp);
2577                return True;
2578
2579             elsif Nkind (S) = N_Block_Statement then
2580                if Present (Declarations (S))
2581                  and then Has_Excluded_Declaration (Declarations (S))
2582                then
2583                   return True;
2584
2585                elsif Present (Handled_Statement_Sequence (S))
2586                   and then
2587                     (Present
2588                       (Exception_Handlers (Handled_Statement_Sequence (S)))
2589                      or else
2590                        Has_Excluded_Statement
2591                          (Statements (Handled_Statement_Sequence (S))))
2592                then
2593                   return True;
2594                end if;
2595
2596             elsif Nkind (S) = N_Case_Statement then
2597                E := First (Alternatives (S));
2598                while Present (E) loop
2599                   if Has_Excluded_Statement (Statements (E)) then
2600                      return True;
2601                   end if;
2602
2603                   Next (E);
2604                end loop;
2605
2606             elsif Nkind (S) = N_If_Statement then
2607                if Has_Excluded_Statement (Then_Statements (S)) then
2608                   return True;
2609                end if;
2610
2611                if Present (Elsif_Parts (S)) then
2612                   E := First (Elsif_Parts (S));
2613                   while Present (E) loop
2614                      if Has_Excluded_Statement (Then_Statements (E)) then
2615                         return True;
2616                      end if;
2617                      Next (E);
2618                   end loop;
2619                end if;
2620
2621                if Present (Else_Statements (S))
2622                  and then Has_Excluded_Statement (Else_Statements (S))
2623                then
2624                   return True;
2625                end if;
2626
2627             elsif Nkind (S) = N_Loop_Statement
2628               and then Has_Excluded_Statement (Statements (S))
2629             then
2630                return True;
2631             end if;
2632
2633             Next (S);
2634          end loop;
2635
2636          return False;
2637       end Has_Excluded_Statement;
2638
2639       -------------------------------
2640       -- Has_Pending_Instantiation --
2641       -------------------------------
2642
2643       function Has_Pending_Instantiation return Boolean is
2644          S : Entity_Id;
2645
2646       begin
2647          S := Current_Scope;
2648          while Present (S) loop
2649             if Is_Compilation_Unit (S)
2650               or else Is_Child_Unit (S)
2651             then
2652                return False;
2653             elsif Ekind (S) = E_Package
2654               and then Has_Forward_Instantiation (S)
2655             then
2656                return True;
2657             end if;
2658
2659             S := Scope (S);
2660          end loop;
2661
2662          return False;
2663       end Has_Pending_Instantiation;
2664
2665       ------------------------
2666       --  Has_Single_Return --
2667       ------------------------
2668
2669       function Has_Single_Return return Boolean is
2670          Return_Statement : Node_Id := Empty;
2671
2672          function Check_Return (N : Node_Id) return Traverse_Result;
2673
2674          ------------------
2675          -- Check_Return --
2676          ------------------
2677
2678          function Check_Return (N : Node_Id) return Traverse_Result is
2679          begin
2680             if Nkind (N) = N_Return_Statement then
2681                if Present (Expression (N))
2682                  and then Is_Entity_Name (Expression (N))
2683                then
2684                   if No (Return_Statement) then
2685                      Return_Statement := N;
2686                      return OK;
2687
2688                   elsif Chars (Expression (N)) =
2689                         Chars (Expression (Return_Statement))
2690                   then
2691                      return OK;
2692
2693                   else
2694                      return Abandon;
2695                   end if;
2696
2697                else
2698                   --  Expression has wrong form
2699
2700                   return Abandon;
2701                end if;
2702
2703             else
2704                return OK;
2705             end if;
2706          end Check_Return;
2707
2708          function Check_All_Returns is new Traverse_Func (Check_Return);
2709
2710       --  Start of processing for Has_Single_Return
2711
2712       begin
2713          return Check_All_Returns (N) = OK
2714            and then Present (Declarations (N))
2715            and then Present (First (Declarations (N)))
2716            and then Chars (Expression (Return_Statement)) =
2717                     Chars (Defining_Identifier (First (Declarations (N))));
2718       end Has_Single_Return;
2719
2720       --------------------
2721       -- Remove_Pragmas --
2722       --------------------
2723
2724       procedure Remove_Pragmas is
2725          Decl : Node_Id;
2726          Nxt  : Node_Id;
2727
2728       begin
2729          Decl := First (Declarations (Body_To_Analyze));
2730          while Present (Decl) loop
2731             Nxt := Next (Decl);
2732
2733             if Nkind (Decl) = N_Pragma
2734               and then Chars (Decl) = Name_Unreferenced
2735             then
2736                Remove (Decl);
2737             end if;
2738
2739             Decl := Nxt;
2740          end loop;
2741       end Remove_Pragmas;
2742
2743       --------------------------
2744       -- Uses_Secondary_Stack --
2745       --------------------------
2746
2747       function Uses_Secondary_Stack (Bod : Node_Id) return Boolean is
2748          function Check_Call (N : Node_Id) return Traverse_Result;
2749          --  Look for function calls that return an unconstrained type
2750
2751          ----------------
2752          -- Check_Call --
2753          ----------------
2754
2755          function Check_Call (N : Node_Id) return Traverse_Result is
2756          begin
2757             if Nkind (N) = N_Function_Call
2758               and then Is_Entity_Name (Name (N))
2759               and then Is_Composite_Type (Etype (Entity (Name (N))))
2760               and then not Is_Constrained (Etype (Entity (Name (N))))
2761             then
2762                Cannot_Inline
2763                  ("cannot inline & (call returns unconstrained type)?",
2764                     N, Subp);
2765                return Abandon;
2766             else
2767                return OK;
2768             end if;
2769          end Check_Call;
2770
2771          function Check_Calls is new Traverse_Func (Check_Call);
2772
2773       begin
2774          return Check_Calls (Bod) = Abandon;
2775       end Uses_Secondary_Stack;
2776
2777    --  Start of processing for Build_Body_To_Inline
2778
2779    begin
2780       if Nkind (Decl) = N_Subprogram_Declaration
2781         and then Present (Body_To_Inline (Decl))
2782       then
2783          return;    --  Done already.
2784
2785       --  Functions that return unconstrained composite types require
2786       --  secondary stack handling, and cannot currently be inlined, unless
2787       --  all return statements return a local variable that is the first
2788       --  local declaration in the body.
2789
2790       elsif Ekind (Subp) = E_Function
2791         and then not Is_Scalar_Type (Etype (Subp))
2792         and then not Is_Access_Type (Etype (Subp))
2793         and then not Is_Constrained (Etype (Subp))
2794       then
2795          if not Has_Single_Return then
2796             Cannot_Inline
2797               ("cannot inline & (unconstrained return type)?", N, Subp);
2798             return;
2799          end if;
2800
2801       --  Ditto for functions that return controlled types, where controlled
2802       --  actions interfere in complex ways with inlining.
2803
2804       elsif Ekind (Subp) = E_Function
2805         and then Controlled_Type (Etype (Subp))
2806       then
2807          Cannot_Inline
2808            ("cannot inline & (controlled return type)?", N, Subp);
2809          return;
2810       end if;
2811
2812       if Present (Declarations (N))
2813         and then Has_Excluded_Declaration (Declarations (N))
2814       then
2815          return;
2816       end if;
2817
2818       if Present (Handled_Statement_Sequence (N)) then
2819          if Present (Exception_Handlers (Handled_Statement_Sequence (N))) then
2820             Cannot_Inline
2821               ("cannot inline& (exception handler)?",
2822                First (Exception_Handlers (Handled_Statement_Sequence (N))),
2823                Subp);
2824             return;
2825          elsif
2826            Has_Excluded_Statement
2827              (Statements (Handled_Statement_Sequence (N)))
2828          then
2829             return;
2830          end if;
2831       end if;
2832
2833       --  We do not inline a subprogram  that is too large, unless it is
2834       --  marked Inline_Always. This pragma does not suppress the other
2835       --  checks on inlining (forbidden declarations, handlers, etc).
2836
2837       if Stat_Count > Max_Size
2838         and then not Is_Always_Inlined (Subp)
2839       then
2840          Cannot_Inline ("cannot inline& (body too large)?", N, Subp);
2841          return;
2842       end if;
2843
2844       if Has_Pending_Instantiation then
2845          Cannot_Inline
2846            ("cannot inline& (forward instance within enclosing body)?",
2847              N, Subp);
2848          return;
2849       end if;
2850
2851       --  Within an instance, the body to inline must be treated as a nested
2852       --  generic, so that the proper global references are preserved.
2853
2854       if In_Instance then
2855          Save_Env (Scope (Current_Scope), Scope (Current_Scope));
2856          Original_Body := Copy_Generic_Node (N, Empty, True);
2857       else
2858          Original_Body := Copy_Separate_Tree (N);
2859       end if;
2860
2861       --  We need to capture references to the formals in order to substitute
2862       --  the actuals at the point of inlining, i.e. instantiation. To treat
2863       --  the formals as globals to the body to inline, we nest it within
2864       --  a dummy parameterless subprogram, declared within the real one.
2865       --  To avoid generating an internal name (which is never public, and
2866       --  which affects serial numbers of other generated names), we use
2867       --  an internal symbol that cannot conflict with user declarations.
2868
2869       Set_Parameter_Specifications (Specification (Original_Body), No_List);
2870       Set_Defining_Unit_Name
2871         (Specification (Original_Body),
2872           Make_Defining_Identifier (Sloc (N), Name_uParent));
2873       Set_Corresponding_Spec (Original_Body, Empty);
2874
2875       Body_To_Analyze := Copy_Generic_Node (Original_Body, Empty, False);
2876
2877       --  Set return type of function, which is also global and does not need
2878       --  to be resolved.
2879
2880       if Ekind (Subp) = E_Function then
2881          Set_Result_Definition (Specification (Body_To_Analyze),
2882            New_Occurrence_Of (Etype (Subp), Sloc (N)));
2883       end if;
2884
2885       if No (Declarations (N)) then
2886          Set_Declarations (N, New_List (Body_To_Analyze));
2887       else
2888          Append (Body_To_Analyze, Declarations (N));
2889       end if;
2890
2891       Expander_Mode_Save_And_Set (False);
2892       Remove_Pragmas;
2893
2894       Analyze (Body_To_Analyze);
2895       Push_Scope (Defining_Entity (Body_To_Analyze));
2896       Save_Global_References (Original_Body);
2897       End_Scope;
2898       Remove (Body_To_Analyze);
2899
2900       Expander_Mode_Restore;
2901
2902       if In_Instance then
2903          Restore_Env;
2904       end if;
2905
2906       --  If secondary stk used there is no point in inlining. We have
2907       --  already issued the warning in this case, so nothing to do.
2908
2909       if Uses_Secondary_Stack (Body_To_Analyze) then
2910          return;
2911       end if;
2912
2913       Set_Body_To_Inline (Decl, Original_Body);
2914       Set_Ekind (Defining_Entity (Original_Body), Ekind (Subp));
2915       Set_Is_Inlined (Subp);
2916    end Build_Body_To_Inline;
2917
2918    -------------------
2919    -- Cannot_Inline --
2920    -------------------
2921
2922    procedure Cannot_Inline (Msg : String; N : Node_Id; Subp : Entity_Id) is
2923    begin
2924       --  Do not emit warning if this is a predefined unit which is not
2925       --  the main unit. With validity checks enabled, some predefined
2926       --  subprograms may contain nested subprograms and become ineligible
2927       --  for inlining.
2928
2929       if Is_Predefined_File_Name (Unit_File_Name (Get_Source_Unit (Subp)))
2930         and then not In_Extended_Main_Source_Unit (Subp)
2931       then
2932          null;
2933
2934       elsif Is_Always_Inlined (Subp) then
2935
2936          --  Remove last character (question mark) to make this into an error,
2937          --  because the Inline_Always pragma cannot be obeyed.
2938
2939          Error_Msg_NE (Msg (Msg'First .. Msg'Last - 1), N, Subp);
2940
2941       elsif Ineffective_Inline_Warnings then
2942          Error_Msg_NE (Msg, N, Subp);
2943       end if;
2944    end Cannot_Inline;
2945
2946    -----------------------
2947    -- Check_Conformance --
2948    -----------------------
2949
2950    procedure Check_Conformance
2951      (New_Id                   : Entity_Id;
2952       Old_Id                   : Entity_Id;
2953       Ctype                    : Conformance_Type;
2954       Errmsg                   : Boolean;
2955       Conforms                 : out Boolean;
2956       Err_Loc                  : Node_Id := Empty;
2957       Get_Inst                 : Boolean := False;
2958       Skip_Controlling_Formals : Boolean := False)
2959    is
2960       procedure Conformance_Error (Msg : String; N : Node_Id := New_Id);
2961       --  Post error message for conformance error on given node. Two messages
2962       --  are output. The first points to the previous declaration with a
2963       --  general "no conformance" message. The second is the detailed reason,
2964       --  supplied as Msg. The parameter N provide information for a possible
2965       --  & insertion in the message, and also provides the location for
2966       --  posting the message in the absence of a specified Err_Loc location.
2967
2968       -----------------------
2969       -- Conformance_Error --
2970       -----------------------
2971
2972       procedure Conformance_Error (Msg : String; N : Node_Id := New_Id) is
2973          Enode : Node_Id;
2974
2975       begin
2976          Conforms := False;
2977
2978          if Errmsg then
2979             if No (Err_Loc) then
2980                Enode := N;
2981             else
2982                Enode := Err_Loc;
2983             end if;
2984
2985             Error_Msg_Sloc := Sloc (Old_Id);
2986
2987             case Ctype is
2988                when Type_Conformant =>
2989                   Error_Msg_N
2990                     ("not type conformant with declaration#!", Enode);
2991
2992                when Mode_Conformant =>
2993                   Error_Msg_N
2994                     ("not mode conformant with declaration#!", Enode);
2995
2996                when Subtype_Conformant =>
2997                   Error_Msg_N
2998                     ("not subtype conformant with declaration#!", Enode);
2999
3000                when Fully_Conformant =>
3001                   Error_Msg_N
3002                     ("not fully conformant with declaration#!", Enode);
3003             end case;
3004
3005             Error_Msg_NE (Msg, Enode, N);
3006          end if;
3007       end Conformance_Error;
3008
3009       --  Local Variables
3010
3011       Old_Type           : constant Entity_Id := Etype (Old_Id);
3012       New_Type           : constant Entity_Id := Etype (New_Id);
3013       Old_Formal         : Entity_Id;
3014       New_Formal         : Entity_Id;
3015       Access_Types_Match : Boolean;
3016       Old_Formal_Base    : Entity_Id;
3017       New_Formal_Base    : Entity_Id;
3018
3019    --  Start of processing for Check_Conformance
3020
3021    begin
3022       Conforms := True;
3023
3024       --  We need a special case for operators, since they don't appear
3025       --  explicitly.
3026
3027       if Ctype = Type_Conformant then
3028          if Ekind (New_Id) = E_Operator
3029            and then Operator_Matches_Spec (New_Id, Old_Id)
3030          then
3031             return;
3032          end if;
3033       end if;
3034
3035       --  If both are functions/operators, check return types conform
3036
3037       if Old_Type /= Standard_Void_Type
3038         and then New_Type /= Standard_Void_Type
3039       then
3040          if not Conforming_Types (Old_Type, New_Type, Ctype, Get_Inst) then
3041             Conformance_Error ("return type does not match!", New_Id);
3042             return;
3043          end if;
3044
3045          --  Ada 2005 (AI-231): In case of anonymous access types check the
3046          --  null-exclusion and access-to-constant attributes match.
3047
3048          if Ada_Version >= Ada_05
3049            and then Ekind (Etype (Old_Type)) = E_Anonymous_Access_Type
3050            and then
3051              (Can_Never_Be_Null (Old_Type)
3052                 /= Can_Never_Be_Null (New_Type)
3053               or else Is_Access_Constant (Etype (Old_Type))
3054                         /= Is_Access_Constant (Etype (New_Type)))
3055          then
3056             Conformance_Error ("return type does not match!", New_Id);
3057             return;
3058          end if;
3059
3060       --  If either is a function/operator and the other isn't, error
3061
3062       elsif Old_Type /= Standard_Void_Type
3063         or else New_Type /= Standard_Void_Type
3064       then
3065          Conformance_Error ("functions can only match functions!", New_Id);
3066          return;
3067       end if;
3068
3069       --  In subtype conformant case, conventions must match (RM 6.3.1(16)).
3070       --  If this is a renaming as body, refine error message to indicate that
3071       --  the conflict is with the original declaration. If the entity is not
3072       --  frozen, the conventions don't have to match, the one of the renamed
3073       --  entity is inherited.
3074
3075       if Ctype >= Subtype_Conformant then
3076          if Convention (Old_Id) /= Convention (New_Id) then
3077
3078             if not Is_Frozen (New_Id) then
3079                null;
3080
3081             elsif Present (Err_Loc)
3082               and then Nkind (Err_Loc) = N_Subprogram_Renaming_Declaration
3083               and then Present (Corresponding_Spec (Err_Loc))
3084             then
3085                Error_Msg_Name_1 := Chars (New_Id);
3086                Error_Msg_Name_2 :=
3087                  Name_Ada + Convention_Id'Pos (Convention (New_Id));
3088
3089                Conformance_Error ("prior declaration for% has convention %!");
3090
3091             else
3092                Conformance_Error ("calling conventions do not match!");
3093             end if;
3094
3095             return;
3096
3097          elsif Is_Formal_Subprogram (Old_Id)
3098            or else Is_Formal_Subprogram (New_Id)
3099          then
3100             Conformance_Error ("formal subprograms not allowed!");
3101             return;
3102          end if;
3103       end if;
3104
3105       --  Deal with parameters
3106
3107       --  Note: we use the entity information, rather than going directly
3108       --  to the specification in the tree. This is not only simpler, but
3109       --  absolutely necessary for some cases of conformance tests between
3110       --  operators, where the declaration tree simply does not exist!
3111
3112       Old_Formal := First_Formal (Old_Id);
3113       New_Formal := First_Formal (New_Id);
3114
3115       while Present (Old_Formal) and then Present (New_Formal) loop
3116          if Is_Controlling_Formal (Old_Formal)
3117            and then Is_Controlling_Formal (New_Formal)
3118            and then Skip_Controlling_Formals
3119          then
3120             goto Skip_Controlling_Formal;
3121          end if;
3122
3123          if Ctype = Fully_Conformant then
3124
3125             --  Names must match. Error message is more accurate if we do
3126             --  this before checking that the types of the formals match.
3127
3128             if Chars (Old_Formal) /= Chars (New_Formal) then
3129                Conformance_Error ("name & does not match!", New_Formal);
3130
3131                --  Set error posted flag on new formal as well to stop
3132                --  junk cascaded messages in some cases.
3133
3134                Set_Error_Posted (New_Formal);
3135                return;
3136             end if;
3137          end if;
3138
3139          --  Ada 2005 (AI-423): Possible access [sub]type and itype match. This
3140          --  case occurs whenever a subprogram is being renamed and one of its
3141          --  parameters imposes a null exclusion. For example:
3142
3143          --     type T is null record;
3144          --     type Acc_T is access T;
3145          --     subtype Acc_T_Sub is Acc_T;
3146
3147          --     procedure P     (Obj : not null Acc_T_Sub);  --  itype
3148          --     procedure Ren_P (Obj :          Acc_T_Sub)   --  subtype
3149          --       renames P;
3150
3151          Old_Formal_Base := Etype (Old_Formal);
3152          New_Formal_Base := Etype (New_Formal);
3153
3154          if Get_Inst then
3155             Old_Formal_Base := Get_Instance_Of (Old_Formal_Base);
3156             New_Formal_Base := Get_Instance_Of (New_Formal_Base);
3157          end if;
3158
3159          Access_Types_Match := Ada_Version >= Ada_05
3160
3161             --  Ensure that this rule is only applied when New_Id is a
3162             --  renaming of Old_Id
3163
3164            and then Nkind (Parent (Parent (New_Id)))
3165                       = N_Subprogram_Renaming_Declaration
3166            and then Nkind (Name (Parent (Parent (New_Id)))) in N_Has_Entity
3167            and then Present (Entity (Name (Parent (Parent (New_Id)))))
3168            and then Entity (Name (Parent (Parent (New_Id)))) = Old_Id
3169
3170             --  Now handle the allowed access-type case
3171
3172            and then Is_Access_Type (Old_Formal_Base)
3173            and then Is_Access_Type (New_Formal_Base)
3174            and then Directly_Designated_Type (Old_Formal_Base) =
3175                       Directly_Designated_Type (New_Formal_Base)
3176            and then ((Is_Itype (Old_Formal_Base)
3177                        and then Can_Never_Be_Null (Old_Formal_Base))
3178                     or else
3179                      (Is_Itype (New_Formal_Base)
3180                        and then Can_Never_Be_Null (New_Formal_Base)));
3181
3182          --  Types must always match. In the visible part of an instance,
3183          --  usual overloading rules for dispatching operations apply, and
3184          --  we check base types (not the actual subtypes).
3185
3186          if In_Instance_Visible_Part
3187            and then Is_Dispatching_Operation (New_Id)
3188          then
3189             if not Conforming_Types
3190                      (T1       => Base_Type (Etype (Old_Formal)),
3191                       T2       => Base_Type (Etype (New_Formal)),
3192                       Ctype    => Ctype,
3193                       Get_Inst => Get_Inst)
3194                and then not Access_Types_Match
3195             then
3196                Conformance_Error ("type of & does not match!", New_Formal);
3197                return;
3198             end if;
3199
3200          elsif not Conforming_Types
3201                      (T1       => Etype (Old_Formal),
3202                       T2       => Etype (New_Formal),
3203                       Ctype    => Ctype,
3204                       Get_Inst => Get_Inst)
3205            and then not Access_Types_Match
3206          then
3207             Conformance_Error ("type of & does not match!", New_Formal);
3208             return;
3209          end if;
3210
3211          --  For mode conformance, mode must match
3212
3213          if Ctype >= Mode_Conformant
3214            and then Parameter_Mode (Old_Formal) /= Parameter_Mode (New_Formal)
3215          then
3216             Conformance_Error ("mode of & does not match!", New_Formal);
3217             return;
3218          end if;
3219
3220          if Ctype >= Subtype_Conformant then
3221
3222             --  Ada 2005 (AI-231): In case of anonymous access types check
3223             --  the null-exclusion and access-to-constant attributes must
3224             --  match.
3225
3226             if Ada_Version >= Ada_05
3227               and then Ekind (Etype (Old_Formal)) = E_Anonymous_Access_Type
3228               and then Ekind (Etype (New_Formal)) = E_Anonymous_Access_Type
3229               and then
3230                 (Can_Never_Be_Null (Old_Formal) /=
3231                  Can_Never_Be_Null (New_Formal)
3232                    or else
3233                  Is_Access_Constant (Etype (Old_Formal)) /=
3234                  Is_Access_Constant (Etype (New_Formal)))
3235             then
3236                --  It is allowed to omit the null-exclusion in case of stream
3237                --  attribute subprograms. We recognize stream subprograms
3238                --  through their TSS-generated suffix.
3239
3240                declare
3241                   TSS_Name : constant TSS_Name_Type := Get_TSS_Name (New_Id);
3242                begin
3243                   if TSS_Name /= TSS_Stream_Read
3244                     and then TSS_Name /= TSS_Stream_Write
3245                     and then TSS_Name /= TSS_Stream_Input
3246                     and then TSS_Name /= TSS_Stream_Output
3247                   then
3248                      Conformance_Error
3249                        ("type of & does not match!", New_Formal);
3250                      return;
3251                   end if;
3252                end;
3253             end if;
3254          end if;
3255
3256          --  Full conformance checks
3257
3258          if Ctype = Fully_Conformant then
3259
3260             --  We have checked already that names match
3261
3262             if Parameter_Mode (Old_Formal) = E_In_Parameter then
3263
3264                --  Check default expressions for in parameters
3265
3266                declare
3267                   NewD : constant Boolean :=
3268                            Present (Default_Value (New_Formal));
3269                   OldD : constant Boolean :=
3270                            Present (Default_Value (Old_Formal));
3271                begin
3272                   if NewD or OldD then
3273
3274                      --  The old default value has been analyzed because the
3275                      --  current full declaration will have frozen everything
3276                      --  before. The new default value has not been analyzed,
3277                      --  so analyze it now before we check for conformance.
3278
3279                      if NewD then
3280                         Push_Scope (New_Id);
3281                         Analyze_Per_Use_Expression
3282                           (Default_Value (New_Formal), Etype (New_Formal));
3283                         End_Scope;
3284                      end if;
3285
3286                      if not (NewD and OldD)
3287                        or else not Fully_Conformant_Expressions
3288                                     (Default_Value (Old_Formal),
3289                                      Default_Value (New_Formal))
3290                      then
3291                         Conformance_Error
3292                           ("default expression for & does not match!",
3293                            New_Formal);
3294                         return;
3295                      end if;
3296                   end if;
3297                end;
3298             end if;
3299          end if;
3300
3301          --  A couple of special checks for Ada 83 mode. These checks are
3302          --  skipped if either entity is an operator in package Standard,
3303          --  or if either old or new instance is not from the source program.
3304
3305          if Ada_Version = Ada_83
3306            and then Sloc (Old_Id) > Standard_Location
3307            and then Sloc (New_Id) > Standard_Location
3308            and then Comes_From_Source (Old_Id)
3309            and then Comes_From_Source (New_Id)
3310          then
3311             declare
3312                Old_Param : constant Node_Id := Declaration_Node (Old_Formal);
3313                New_Param : constant Node_Id := Declaration_Node (New_Formal);
3314
3315             begin
3316                --  Explicit IN must be present or absent in both cases. This
3317                --  test is required only in the full conformance case.
3318
3319                if In_Present (Old_Param) /= In_Present (New_Param)
3320                  and then Ctype = Fully_Conformant
3321                then
3322                   Conformance_Error
3323                     ("(Ada 83) IN must appear in both declarations",
3324                      New_Formal);
3325                   return;
3326                end if;
3327
3328                --  Grouping (use of comma in param lists) must be the same
3329                --  This is where we catch a misconformance like:
3330
3331                --    A, B : Integer
3332                --    A : Integer; B : Integer
3333
3334                --  which are represented identically in the tree except
3335                --  for the setting of the flags More_Ids and Prev_Ids.
3336
3337                if More_Ids (Old_Param) /= More_Ids (New_Param)
3338                  or else Prev_Ids (Old_Param) /= Prev_Ids (New_Param)
3339                then
3340                   Conformance_Error
3341                     ("grouping of & does not match!", New_Formal);
3342                   return;
3343                end if;
3344             end;
3345          end if;
3346
3347          --  This label is required when skipping controlling formals
3348
3349          <<Skip_Controlling_Formal>>
3350
3351          Next_Formal (Old_Formal);
3352          Next_Formal (New_Formal);
3353       end loop;
3354
3355       if Present (Old_Formal) then
3356          Conformance_Error ("too few parameters!");
3357          return;
3358
3359       elsif Present (New_Formal) then
3360          Conformance_Error ("too many parameters!", New_Formal);
3361          return;
3362       end if;
3363    end Check_Conformance;
3364
3365    -----------------------
3366    -- Check_Conventions --
3367    -----------------------
3368
3369    procedure Check_Conventions (Typ : Entity_Id) is
3370
3371       function Skip_Check (Op : Entity_Id) return Boolean;
3372       pragma Inline (Skip_Check);
3373       --  A small optimization: skip the predefined dispatching operations,
3374       --  since they always have the same convention. Also do not consider
3375       --  abstract primitives since those are left by an erroneous overriding.
3376       --  This function returns True for any operation that is thus exempted
3377       --  exempted from checking.
3378
3379       procedure Check_Convention
3380         (Op          : Entity_Id;
3381          Search_From : Elmt_Id);
3382       --  Verify that the convention of inherited dispatching operation Op is
3383       --  consistent among all subprograms it overrides. In order to minimize
3384       --  the search, Search_From is utilized to designate a specific point in
3385       --  the list rather than iterating over the whole list once more.
3386
3387       ----------------------
3388       -- Check_Convention --
3389       ----------------------
3390
3391       procedure Check_Convention
3392         (Op          : Entity_Id;
3393          Search_From : Elmt_Id)
3394       is
3395          procedure Error_Msg_Operation (Op : Entity_Id);
3396          --  Emit a continuation to an error message depicting the kind, name,
3397          --  convention and source location of subprogram Op.
3398
3399          -------------------------
3400          -- Error_Msg_Operation --
3401          -------------------------
3402
3403          procedure Error_Msg_Operation (Op : Entity_Id) is
3404          begin
3405             Error_Msg_Name_1 := Chars (Op);
3406
3407             --  Error messages of primitive subprograms do not contain a
3408             --  convention attribute since the convention may have been first
3409             --  inherited from a parent subprogram, then changed by a pragma.
3410
3411             if Comes_From_Source (Op) then
3412                Error_Msg_Sloc := Sloc (Op);
3413                Error_Msg_N
3414                 ("\ primitive % defined #", Typ);
3415
3416             else
3417                Error_Msg_Name_2 := Get_Convention_Name (Convention (Op));
3418
3419                if Present (Abstract_Interface_Alias (Op)) then
3420                   Error_Msg_Sloc := Sloc (Abstract_Interface_Alias (Op));
3421                   Error_Msg_N ("\\overridden operation % with " &
3422                                "convention % defined #", Typ);
3423
3424                else pragma Assert (Present (Alias (Op)));
3425                   Error_Msg_Sloc := Sloc (Alias (Op));
3426                   Error_Msg_N ("\\inherited operation % with " &
3427                                "convention % defined #", Typ);
3428                end if;
3429             end if;
3430          end Error_Msg_Operation;
3431
3432          --  Local variables
3433
3434          Second_Prim_Op      : Entity_Id;
3435          Second_Prim_Op_Elmt : Elmt_Id;
3436
3437       --  Start of processing for Check_Convention
3438
3439       begin
3440          Second_Prim_Op_Elmt := Next_Elmt (Search_From);
3441          while Present (Second_Prim_Op_Elmt) loop
3442             Second_Prim_Op := Node (Second_Prim_Op_Elmt);
3443
3444             if not Skip_Check (Second_Prim_Op)
3445               and then Chars (Second_Prim_Op) = Chars (Op)
3446               and then Type_Conformant (Second_Prim_Op, Op)
3447               and then Convention (Second_Prim_Op) /= Convention (Op)
3448             then
3449                Error_Msg_N
3450                  ("inconsistent conventions in primitive operations", Typ);
3451
3452                Error_Msg_Operation (Op);
3453                Error_Msg_Operation (Second_Prim_Op);
3454
3455                --  Avoid cascading errors
3456
3457                return;
3458             end if;
3459
3460             Next_Elmt (Second_Prim_Op_Elmt);
3461          end loop;
3462       end Check_Convention;
3463
3464       ----------------
3465       -- Skip_Check --
3466       ----------------
3467
3468       function Skip_Check (Op : Entity_Id) return Boolean is
3469       begin
3470          return Is_Predefined_Dispatching_Operation (Op)
3471            or else Is_Abstract_Subprogram (Op);
3472       end Skip_Check;
3473
3474       --  Local variables
3475
3476       Prim_Op      : Entity_Id;
3477       Prim_Op_Elmt : Elmt_Id;
3478
3479    --  Start of processing for Check_Conventions
3480
3481    begin
3482       --  The algorithm checks every overriding dispatching operation against
3483       --  all the corresponding overridden dispatching operations, detecting
3484       --  differences in coventions.
3485
3486       Prim_Op_Elmt := First_Elmt (Primitive_Operations (Typ));
3487       while Present (Prim_Op_Elmt) loop
3488          Prim_Op := Node (Prim_Op_Elmt);
3489
3490          --  A small optimization: skip the predefined dispatching operations
3491          --  since they always have the same convention. Also avoid processing
3492          --  of abstract primitives left from an erroneous overriding.
3493
3494          if not Skip_Check (Prim_Op) then
3495             Check_Convention
3496               (Op          => Prim_Op,
3497                Search_From => Prim_Op_Elmt);
3498          end if;
3499
3500          Next_Elmt (Prim_Op_Elmt);
3501       end loop;
3502    end Check_Conventions;
3503
3504    ------------------------------
3505    -- Check_Delayed_Subprogram --
3506    ------------------------------
3507
3508    procedure Check_Delayed_Subprogram (Designator : Entity_Id) is
3509       F : Entity_Id;
3510
3511       procedure Possible_Freeze (T : Entity_Id);
3512       --  T is the type of either a formal parameter or of the return type.
3513       --  If T is not yet frozen and needs a delayed freeze, then the
3514       --  subprogram itself must be delayed.
3515
3516       ---------------------
3517       -- Possible_Freeze --
3518       ---------------------
3519
3520       procedure Possible_Freeze (T : Entity_Id) is
3521       begin
3522          if Has_Delayed_Freeze (T)
3523            and then not Is_Frozen (T)
3524          then
3525             Set_Has_Delayed_Freeze (Designator);
3526
3527          elsif Is_Access_Type (T)
3528            and then Has_Delayed_Freeze (Designated_Type (T))
3529            and then not Is_Frozen (Designated_Type (T))
3530          then
3531             Set_Has_Delayed_Freeze (Designator);
3532          end if;
3533       end Possible_Freeze;
3534
3535    --  Start of processing for Check_Delayed_Subprogram
3536
3537    begin
3538       --  Never need to freeze abstract subprogram
3539
3540       if Ekind (Designator) /= E_Subprogram_Type
3541         and then Is_Abstract_Subprogram (Designator)
3542       then
3543          null;
3544       else
3545          --  Need delayed freeze if return type itself needs a delayed
3546          --  freeze and is not yet frozen.
3547
3548          Possible_Freeze (Etype (Designator));
3549          Possible_Freeze (Base_Type (Etype (Designator))); -- needed ???
3550
3551          --  Need delayed freeze if any of the formal types themselves need
3552          --  a delayed freeze and are not yet frozen.
3553
3554          F := First_Formal (Designator);
3555          while Present (F) loop
3556             Possible_Freeze (Etype (F));
3557             Possible_Freeze (Base_Type (Etype (F))); -- needed ???
3558             Next_Formal (F);
3559          end loop;
3560       end if;
3561
3562       --  Mark functions that return by reference. Note that it cannot be
3563       --  done for delayed_freeze subprograms because the underlying
3564       --  returned type may not be known yet (for private types)
3565
3566       if not Has_Delayed_Freeze (Designator)
3567         and then Expander_Active
3568       then
3569          declare
3570             Typ  : constant Entity_Id := Etype (Designator);
3571             Utyp : constant Entity_Id := Underlying_Type (Typ);
3572
3573          begin
3574             if Is_Inherently_Limited_Type (Typ) then
3575                Set_Returns_By_Ref (Designator);
3576
3577             elsif Present (Utyp) and then CW_Or_Controlled_Type (Utyp) then
3578                Set_Returns_By_Ref (Designator);
3579             end if;
3580          end;
3581       end if;
3582    end Check_Delayed_Subprogram;
3583
3584    ------------------------------------
3585    -- Check_Discriminant_Conformance --
3586    ------------------------------------
3587
3588    procedure Check_Discriminant_Conformance
3589      (N        : Node_Id;
3590       Prev     : Entity_Id;
3591       Prev_Loc : Node_Id)
3592    is
3593       Old_Discr      : Entity_Id := First_Discriminant (Prev);
3594       New_Discr      : Node_Id   := First (Discriminant_Specifications (N));
3595       New_Discr_Id   : Entity_Id;
3596       New_Discr_Type : Entity_Id;
3597
3598       procedure Conformance_Error (Msg : String; N : Node_Id);
3599       --  Post error message for conformance error on given node. Two messages
3600       --  are output. The first points to the previous declaration with a
3601       --  general "no conformance" message. The second is the detailed reason,
3602       --  supplied as Msg. The parameter N provide information for a possible
3603       --  & insertion in the message.
3604
3605       -----------------------
3606       -- Conformance_Error --
3607       -----------------------
3608
3609       procedure Conformance_Error (Msg : String; N : Node_Id) is
3610       begin
3611          Error_Msg_Sloc := Sloc (Prev_Loc);
3612          Error_Msg_N ("not fully conformant with declaration#!", N);
3613          Error_Msg_NE (Msg, N, N);
3614       end Conformance_Error;
3615
3616    --  Start of processing for Check_Discriminant_Conformance
3617
3618    begin
3619       while Present (Old_Discr) and then Present (New_Discr) loop
3620
3621          New_Discr_Id := Defining_Identifier (New_Discr);
3622
3623          --  The subtype mark of the discriminant on the full type has not
3624          --  been analyzed so we do it here. For an access discriminant a new
3625          --  type is created.
3626
3627          if Nkind (Discriminant_Type (New_Discr)) = N_Access_Definition then
3628             New_Discr_Type :=
3629               Access_Definition (N, Discriminant_Type (New_Discr));
3630
3631          else
3632             Analyze (Discriminant_Type (New_Discr));
3633             New_Discr_Type := Etype (Discriminant_Type (New_Discr));
3634          end if;
3635
3636          if not Conforming_Types
3637                   (Etype (Old_Discr), New_Discr_Type, Fully_Conformant)
3638          then
3639             Conformance_Error ("type of & does not match!", New_Discr_Id);
3640             return;
3641          else
3642             --  Treat the new discriminant as an occurrence of the old one,
3643             --  for navigation purposes, and fill in some semantic
3644             --  information, for completeness.
3645
3646             Generate_Reference (Old_Discr, New_Discr_Id, 'r');
3647             Set_Etype (New_Discr_Id, Etype (Old_Discr));
3648             Set_Scope (New_Discr_Id, Scope (Old_Discr));
3649          end if;
3650
3651          --  Names must match
3652
3653          if Chars (Old_Discr) /= Chars (Defining_Identifier (New_Discr)) then
3654             Conformance_Error ("name & does not match!", New_Discr_Id);
3655             return;
3656          end if;
3657
3658          --  Default expressions must match
3659
3660          declare
3661             NewD : constant Boolean :=
3662                      Present (Expression (New_Discr));
3663             OldD : constant Boolean :=
3664                      Present (Expression (Parent (Old_Discr)));
3665
3666          begin
3667             if NewD or OldD then
3668
3669                --  The old default value has been analyzed and expanded,
3670                --  because the current full declaration will have frozen
3671                --  everything before. The new default values have not been
3672                --  expanded, so expand now to check conformance.
3673
3674                if NewD then
3675                   Analyze_Per_Use_Expression
3676                     (Expression (New_Discr), New_Discr_Type);
3677                end if;
3678
3679                if not (NewD and OldD)
3680                  or else not Fully_Conformant_Expressions
3681                               (Expression (Parent (Old_Discr)),
3682                                Expression (New_Discr))
3683
3684                then
3685                   Conformance_Error
3686                     ("default expression for & does not match!",
3687                      New_Discr_Id);
3688                   return;
3689                end if;
3690             end if;
3691          end;
3692
3693          --  In Ada 83 case, grouping must match: (A,B : X) /= (A : X; B : X)
3694
3695          if Ada_Version = Ada_83 then
3696             declare
3697                Old_Disc : constant Node_Id := Declaration_Node (Old_Discr);
3698
3699             begin
3700                --  Grouping (use of comma in param lists) must be the same
3701                --  This is where we catch a misconformance like:
3702
3703                --    A,B : Integer
3704                --    A : Integer; B : Integer
3705
3706                --  which are represented identically in the tree except
3707                --  for the setting of the flags More_Ids and Prev_Ids.
3708
3709                if More_Ids (Old_Disc) /= More_Ids (New_Discr)
3710                  or else Prev_Ids (Old_Disc) /= Prev_Ids (New_Discr)
3711                then
3712                   Conformance_Error
3713                     ("grouping of & does not match!", New_Discr_Id);
3714                   return;
3715                end if;
3716             end;
3717          end if;
3718
3719          Next_Discriminant (Old_Discr);
3720          Next (New_Discr);
3721       end loop;
3722
3723       if Present (Old_Discr) then
3724          Conformance_Error ("too few discriminants!", Defining_Identifier (N));
3725          return;
3726
3727       elsif Present (New_Discr) then
3728          Conformance_Error
3729            ("too many discriminants!", Defining_Identifier (New_Discr));
3730          return;
3731       end if;
3732    end Check_Discriminant_Conformance;
3733
3734    ----------------------------
3735    -- Check_Fully_Conformant --
3736    ----------------------------
3737
3738    procedure Check_Fully_Conformant
3739      (New_Id  : Entity_Id;
3740       Old_Id  : Entity_Id;
3741       Err_Loc : Node_Id := Empty)
3742    is
3743       Result : Boolean;
3744    begin
3745       Check_Conformance
3746         (New_Id, Old_Id, Fully_Conformant, True, Result, Err_Loc);
3747    end Check_Fully_Conformant;
3748
3749    ---------------------------
3750    -- Check_Mode_Conformant --
3751    ---------------------------
3752
3753    procedure Check_Mode_Conformant
3754      (New_Id   : Entity_Id;
3755       Old_Id   : Entity_Id;
3756       Err_Loc  : Node_Id := Empty;
3757       Get_Inst : Boolean := False)
3758    is
3759       Result : Boolean;
3760
3761    begin
3762       Check_Conformance
3763         (New_Id, Old_Id, Mode_Conformant, True, Result, Err_Loc, Get_Inst);
3764    end Check_Mode_Conformant;
3765
3766    --------------------------------
3767    -- Check_Overriding_Indicator --
3768    --------------------------------
3769
3770    procedure Check_Overriding_Indicator
3771      (Subp            : Entity_Id;
3772       Overridden_Subp : Entity_Id := Empty)
3773    is
3774       Decl : Node_Id;
3775       Spec : Node_Id;
3776
3777    begin
3778       --  No overriding indicator for literals
3779
3780       if Ekind (Subp) = E_Enumeration_Literal then
3781          return;
3782
3783       elsif Ekind (Subp) = E_Entry then
3784          Decl := Parent (Subp);
3785
3786       else
3787          Decl := Unit_Declaration_Node (Subp);
3788       end if;
3789
3790       if Nkind (Decl) = N_Subprogram_Body
3791         or else Nkind (Decl) = N_Subprogram_Body_Stub
3792         or else Nkind (Decl) = N_Subprogram_Declaration
3793         or else Nkind (Decl) = N_Abstract_Subprogram_Declaration
3794         or else Nkind (Decl) = N_Subprogram_Renaming_Declaration
3795       then
3796          Spec := Specification (Decl);
3797
3798       elsif Nkind (Decl) = N_Entry_Declaration then
3799          Spec := Decl;
3800
3801       else
3802          return;
3803       end if;
3804
3805       if Present (Overridden_Subp) then
3806          if Must_Not_Override (Spec) then
3807             Error_Msg_Sloc := Sloc (Overridden_Subp);
3808
3809             if Ekind (Subp) = E_Entry then
3810                Error_Msg_NE ("entry & overrides inherited operation #",
3811                              Spec, Subp);
3812
3813             else
3814                Error_Msg_NE ("subprogram & overrides inherited operation #",
3815                              Spec, Subp);
3816             end if;
3817          end if;
3818
3819       --  If Subp is an operator, it may override a predefined operation.
3820       --  In that case overridden_subp is empty because of our implicit
3821       --  representation for predefined operators. We have to check whether
3822       --  the signature of Subp matches that of a predefined operator.
3823       --  Note that first argument provides the name of the operator, and
3824       --  the second argument the signature that may match that of a standard
3825       --  operation.
3826
3827       elsif Nkind (Subp) = N_Defining_Operator_Symbol
3828         and then  Must_Not_Override (Spec)
3829       then
3830          if Operator_Matches_Spec (Subp, Subp) then
3831             Error_Msg_NE
3832               ("subprogram & overrides predefined operation ",
3833                  Spec, Subp);
3834          end if;
3835
3836       else
3837          if Must_Override (Spec) then
3838             if Ekind (Subp) = E_Entry then
3839                Error_Msg_NE ("entry & is not overriding", Spec, Subp);
3840
3841             elsif Nkind (Subp) = N_Defining_Operator_Symbol then
3842                if not Operator_Matches_Spec (Subp, Subp) then
3843                   Error_Msg_NE
3844                     ("subprogram & is not overriding", Spec, Subp);
3845                end if;
3846
3847             else
3848                Error_Msg_NE ("subprogram & is not overriding", Spec, Subp);
3849             end if;
3850          end if;
3851       end if;
3852    end Check_Overriding_Indicator;
3853
3854    -------------------
3855    -- Check_Returns --
3856    -------------------
3857
3858    --  Note: this procedure needs to know far too much about how the expander
3859    --  messes with exceptions. The use of the flag Exception_Junk and the
3860    --  incorporation of knowledge of Exp_Ch11.Expand_Local_Exception_Handlers
3861    --  works, but is not very clean. It would be better if the expansion
3862    --  routines would leave Original_Node working nicely, and we could use
3863    --  Original_Node here to ignore all the peculiar expander messing ???
3864
3865    procedure Check_Returns
3866      (HSS  : Node_Id;
3867       Mode : Character;
3868       Err  : out Boolean;
3869       Proc : Entity_Id := Empty)
3870    is
3871       Handler : Node_Id;
3872
3873       procedure Check_Statement_Sequence (L : List_Id);
3874       --  Internal recursive procedure to check a list of statements for proper
3875       --  termination by a return statement (or a transfer of control or a
3876       --  compound statement that is itself internally properly terminated).
3877
3878       ------------------------------
3879       -- Check_Statement_Sequence --
3880       ------------------------------
3881
3882       procedure Check_Statement_Sequence (L : List_Id) is
3883          Last_Stm : Node_Id;
3884          Stm      : Node_Id;
3885          Kind     : Node_Kind;
3886
3887          Raise_Exception_Call : Boolean;
3888          --  Set True if statement sequence terminated by Raise_Exception call
3889          --  or a Reraise_Occurrence call.
3890
3891       begin
3892          Raise_Exception_Call := False;
3893
3894          --  Get last real statement
3895
3896          Last_Stm := Last (L);
3897
3898          --  Deal with digging out exception handler statement sequences that
3899          --  have been transformed by the local raise to goto optimization.
3900          --  See Exp_Ch11.Expand_Local_Exception_Handlers for details. If this
3901          --  optimization has occurred, we are looking at something like:
3902
3903          --  begin
3904          --     original stmts in block
3905
3906          --  exception            \
3907          --     when excep1 =>     |
3908          --        goto L1;        | omitted if No_Exception_Propagation
3909          --     when excep2 =>     |
3910          --        goto L2;       /
3911          --  end;
3912
3913          --  goto L3;      -- skip handler when exception not raised
3914
3915          --  <<L1>>        -- target label for local exception
3916          --     begin
3917          --        estmts1
3918          --     end;
3919
3920          --     goto L3;
3921
3922          --  <<L2>>
3923          --     begin
3924          --        estmts2
3925          --     end;
3926
3927          --  <<L3>>
3928
3929          --  and what we have to do is to dig out the estmts1 and estmts2
3930          --  sequences (which were the original sequences of statements in
3931          --  the exception handlers) and check them.
3932
3933          if Nkind (Last_Stm) = N_Label
3934            and then Exception_Junk (Last_Stm)
3935          then
3936             Stm := Last_Stm;
3937             loop
3938                Prev (Stm);
3939                exit when No (Stm);
3940                exit when Nkind (Stm) /= N_Block_Statement;
3941                exit when not Exception_Junk (Stm);
3942                Prev (Stm);
3943                exit when No (Stm);
3944                exit when Nkind (Stm) /= N_Label;
3945                exit when not Exception_Junk (Stm);
3946                Check_Statement_Sequence
3947                  (Statements (Handled_Statement_Sequence (Next (Stm))));
3948
3949                Prev (Stm);
3950                Last_Stm := Stm;
3951                exit when No (Stm);
3952                exit when Nkind (Stm) /= N_Goto_Statement;
3953                exit when not Exception_Junk (Stm);
3954             end loop;
3955          end if;
3956
3957          --  Don't count pragmas
3958
3959          while Nkind (Last_Stm) = N_Pragma
3960
3961          --  Don't count call to SS_Release (can happen after Raise_Exception)
3962
3963            or else
3964              (Nkind (Last_Stm) = N_Procedure_Call_Statement
3965                 and then
3966               Nkind (Name (Last_Stm)) = N_Identifier
3967                 and then
3968               Is_RTE (Entity (Name (Last_Stm)), RE_SS_Release))
3969
3970          --  Don't count exception junk
3971
3972            or else
3973              ((Nkind (Last_Stm) = N_Goto_Statement
3974                  or else Nkind (Last_Stm) = N_Label
3975                  or else Nkind (Last_Stm) = N_Object_Declaration)
3976                 and then Exception_Junk (Last_Stm))
3977            or else Nkind (Last_Stm) in N_Push_xxx_Label
3978            or else Nkind (Last_Stm) in N_Pop_xxx_Label
3979          loop
3980             Prev (Last_Stm);
3981          end loop;
3982
3983          --  Here we have the "real" last statement
3984
3985          Kind := Nkind (Last_Stm);
3986
3987          --  Transfer of control, OK. Note that in the No_Return procedure
3988          --  case, we already diagnosed any explicit return statements, so
3989          --  we can treat them as OK in this context.
3990
3991          if Is_Transfer (Last_Stm) then
3992             return;
3993
3994          --  Check cases of explicit non-indirect procedure calls
3995
3996          elsif Kind = N_Procedure_Call_Statement
3997            and then Is_Entity_Name (Name (Last_Stm))
3998          then
3999             --  Check call to Raise_Exception procedure which is treated
4000             --  specially, as is a call to Reraise_Occurrence.
4001
4002             --  We suppress the warning in these cases since it is likely that
4003             --  the programmer really does not expect to deal with the case
4004             --  of Null_Occurrence, and thus would find a warning about a
4005             --  missing return curious, and raising Program_Error does not
4006             --  seem such a bad behavior if this does occur.
4007
4008             --  Note that in the Ada 2005 case for Raise_Exception, the actual
4009             --  behavior will be to raise Constraint_Error (see AI-329).
4010
4011             if Is_RTE (Entity (Name (Last_Stm)), RE_Raise_Exception)
4012                  or else
4013                Is_RTE (Entity (Name (Last_Stm)), RE_Reraise_Occurrence)
4014             then
4015                Raise_Exception_Call := True;
4016
4017                --  For Raise_Exception call, test first argument, if it is
4018                --  an attribute reference for a 'Identity call, then we know
4019                --  that the call cannot possibly return.
4020
4021                declare
4022                   Arg : constant Node_Id :=
4023                           Original_Node (First_Actual (Last_Stm));
4024                begin
4025                   if Nkind (Arg) = N_Attribute_Reference
4026                     and then Attribute_Name (Arg) = Name_Identity
4027                   then
4028                      return;
4029                   end if;
4030                end;
4031             end if;
4032
4033          --  If statement, need to look inside if there is an else and check
4034          --  each constituent statement sequence for proper termination.
4035
4036          elsif Kind = N_If_Statement
4037            and then Present (Else_Statements (Last_Stm))
4038          then
4039             Check_Statement_Sequence (Then_Statements (Last_Stm));
4040             Check_Statement_Sequence (Else_Statements (Last_Stm));
4041
4042             if Present (Elsif_Parts (Last_Stm)) then
4043                declare
4044                   Elsif_Part : Node_Id := First (Elsif_Parts (Last_Stm));
4045
4046                begin
4047                   while Present (Elsif_Part) loop
4048                      Check_Statement_Sequence (Then_Statements (Elsif_Part));
4049                      Next (Elsif_Part);
4050                   end loop;
4051                end;
4052             end if;
4053
4054             return;
4055
4056          --  Case statement, check each case for proper termination
4057
4058          elsif Kind = N_Case_Statement then
4059             declare
4060                Case_Alt : Node_Id;
4061
4062             begin
4063                Case_Alt := First_Non_Pragma (Alternatives (Last_Stm));
4064                while Present (Case_Alt) loop
4065                   Check_Statement_Sequence (Statements (Case_Alt));
4066                   Next_Non_Pragma (Case_Alt);
4067                end loop;
4068             end;
4069
4070             return;
4071
4072          --  Block statement, check its handled sequence of statements
4073
4074          elsif Kind = N_Block_Statement then
4075             declare
4076                Err1 : Boolean;
4077
4078             begin
4079                Check_Returns
4080                  (Handled_Statement_Sequence (Last_Stm), Mode, Err1);
4081
4082                if Err1 then
4083                   Err := True;
4084                end if;
4085
4086                return;
4087             end;
4088
4089          --  Loop statement. If there is an iteration scheme, we can definitely
4090          --  fall out of the loop. Similarly if there is an exit statement, we
4091          --  can fall out. In either case we need a following return.
4092
4093          elsif Kind = N_Loop_Statement then
4094             if Present (Iteration_Scheme (Last_Stm))
4095               or else Has_Exit (Entity (Identifier (Last_Stm)))
4096             then
4097                null;
4098
4099             --  A loop with no exit statement or iteration scheme if either
4100             --  an inifite loop, or it has some other exit (raise/return).
4101             --  In either case, no warning is required.
4102
4103             else
4104                return;
4105             end if;
4106
4107          --  Timed entry call, check entry call and delay alternatives
4108
4109          --  Note: in expanded code, the timed entry call has been converted
4110          --  to a set of expanded statements on which the check will work
4111          --  correctly in any case.
4112
4113          elsif Kind = N_Timed_Entry_Call then
4114             declare
4115                ECA : constant Node_Id := Entry_Call_Alternative (Last_Stm);
4116                DCA : constant Node_Id := Delay_Alternative      (Last_Stm);
4117
4118             begin
4119                --  If statement sequence of entry call alternative is missing,
4120                --  then we can definitely fall through, and we post the error
4121                --  message on the entry call alternative itself.
4122
4123                if No (Statements (ECA)) then
4124                   Last_Stm := ECA;
4125
4126                --  If statement sequence of delay alternative is missing, then
4127                --  we can definitely fall through, and we post the error
4128                --  message on the delay alternative itself.
4129
4130                --  Note: if both ECA and DCA are missing the return, then we
4131                --  post only one message, should be enough to fix the bugs.
4132                --  If not we will get a message next time on the DCA when the
4133                --  ECA is fixed!
4134
4135                elsif No (Statements (DCA)) then
4136                   Last_Stm := DCA;
4137
4138                --  Else check both statement sequences
4139
4140                else
4141                   Check_Statement_Sequence (Statements (ECA));
4142                   Check_Statement_Sequence (Statements (DCA));
4143                   return;
4144                end if;
4145             end;
4146
4147          --  Conditional entry call, check entry call and else part
4148
4149          --  Note: in expanded code, the conditional entry call has been
4150          --  converted to a set of expanded statements on which the check
4151          --  will work correctly in any case.
4152
4153          elsif Kind = N_Conditional_Entry_Call then
4154             declare
4155                ECA : constant Node_Id := Entry_Call_Alternative (Last_Stm);
4156
4157             begin
4158                --  If statement sequence of entry call alternative is missing,
4159                --  then we can definitely fall through, and we post the error
4160                --  message on the entry call alternative itself.
4161
4162                if No (Statements (ECA)) then
4163                   Last_Stm := ECA;
4164
4165                --  Else check statement sequence and else part
4166
4167                else
4168                   Check_Statement_Sequence (Statements (ECA));
4169                   Check_Statement_Sequence (Else_Statements (Last_Stm));
4170                   return;
4171                end if;
4172             end;
4173          end if;
4174
4175          --  If we fall through, issue appropriate message
4176
4177          if Mode = 'F' then
4178             if not Raise_Exception_Call then
4179                Error_Msg_N
4180                  ("?RETURN statement missing following this statement",
4181                   Last_Stm);
4182                Error_Msg_N
4183                  ("\?Program_Error may be raised at run time",
4184                   Last_Stm);
4185             end if;
4186
4187             --  Note: we set Err even though we have not issued a warning
4188             --  because we still have a case of a missing return. This is
4189             --  an extremely marginal case, probably will never be noticed
4190             --  but we might as well get it right.
4191
4192             Err := True;
4193
4194          --  Otherwise we have the case of a procedure marked No_Return
4195
4196          else
4197             Error_Msg_N
4198               ("?implied return after this statement will raise Program_Error",
4199                Last_Stm);
4200             Error_Msg_NE
4201               ("?procedure & is marked as No_Return",
4202                Last_Stm, Proc);
4203
4204             declare
4205                RE : constant Node_Id :=
4206                       Make_Raise_Program_Error (Sloc (Last_Stm),
4207                         Reason => PE_Implicit_Return);
4208             begin
4209                Insert_After (Last_Stm, RE);
4210                Analyze (RE);
4211             end;
4212          end if;
4213       end Check_Statement_Sequence;
4214
4215    --  Start of processing for Check_Returns
4216
4217    begin
4218       Err := False;
4219       Check_Statement_Sequence (Statements (HSS));
4220
4221       if Present (Exception_Handlers (HSS)) then
4222          Handler := First_Non_Pragma (Exception_Handlers (HSS));
4223          while Present (Handler) loop
4224             Check_Statement_Sequence (Statements (Handler));
4225             Next_Non_Pragma (Handler);
4226          end loop;
4227       end if;
4228    end Check_Returns;
4229
4230    ----------------------------
4231    -- Check_Subprogram_Order --
4232    ----------------------------
4233
4234    procedure Check_Subprogram_Order (N : Node_Id) is
4235
4236       function Subprogram_Name_Greater (S1, S2 : String) return Boolean;
4237       --  This is used to check if S1 > S2 in the sense required by this
4238       --  test, for example nameab < namec, but name2 < name10.
4239
4240       -----------------------------
4241       -- Subprogram_Name_Greater --
4242       -----------------------------
4243
4244       function Subprogram_Name_Greater (S1, S2 : String) return Boolean is
4245          L1, L2 : Positive;
4246          N1, N2 : Natural;
4247
4248       begin
4249          --  Remove trailing numeric parts
4250
4251          L1 := S1'Last;
4252          while S1 (L1) in '0' .. '9' loop
4253             L1 := L1 - 1;
4254          end loop;
4255
4256          L2 := S2'Last;
4257          while S2 (L2) in '0' .. '9' loop
4258             L2 := L2 - 1;
4259          end loop;
4260
4261          --  If non-numeric parts non-equal, that's decisive
4262
4263          if S1 (S1'First .. L1) < S2 (S2'First .. L2) then
4264             return False;
4265
4266          elsif S1 (S1'First .. L1) > S2 (S2'First .. L2) then
4267             return True;
4268
4269          --  If non-numeric parts equal, compare suffixed numeric parts. Note
4270          --  that a missing suffix is treated as numeric zero in this test.
4271
4272          else
4273             N1 := 0;
4274             while L1 < S1'Last loop
4275                L1 := L1 + 1;
4276                N1 := N1 * 10 + Character'Pos (S1 (L1)) - Character'Pos ('0');
4277             end loop;
4278
4279             N2 := 0;
4280             while L2 < S2'Last loop
4281                L2 := L2 + 1;
4282                N2 := N2 * 10 + Character'Pos (S2 (L2)) - Character'Pos ('0');
4283             end loop;
4284
4285             return N1 > N2;
4286          end if;
4287       end Subprogram_Name_Greater;
4288
4289    --  Start of processing for Check_Subprogram_Order
4290
4291    begin
4292       --  Check body in alpha order if this is option
4293
4294       if Style_Check
4295         and then Style_Check_Order_Subprograms
4296         and then Nkind (N) = N_Subprogram_Body
4297         and then Comes_From_Source (N)
4298         and then In_Extended_Main_Source_Unit (N)
4299       then
4300          declare
4301             LSN : String_Ptr
4302                     renames Scope_Stack.Table
4303                               (Scope_Stack.Last).Last_Subprogram_Name;
4304
4305             Body_Id : constant Entity_Id :=
4306                         Defining_Entity (Specification (N));
4307
4308          begin
4309             Get_Decoded_Name_String (Chars (Body_Id));
4310
4311             if LSN /= null then
4312                if Subprogram_Name_Greater
4313                     (LSN.all, Name_Buffer (1 .. Name_Len))
4314                then
4315                   Style.Subprogram_Not_In_Alpha_Order (Body_Id);
4316                end if;
4317
4318                Free (LSN);
4319             end if;
4320
4321             LSN := new String'(Name_Buffer (1 .. Name_Len));
4322          end;
4323       end if;
4324    end Check_Subprogram_Order;
4325
4326    ------------------------------
4327    -- Check_Subtype_Conformant --
4328    ------------------------------
4329
4330    procedure Check_Subtype_Conformant
4331      (New_Id  : Entity_Id;
4332       Old_Id  : Entity_Id;
4333       Err_Loc : Node_Id := Empty)
4334    is
4335       Result : Boolean;
4336    begin
4337       Check_Conformance
4338         (New_Id, Old_Id, Subtype_Conformant, True, Result, Err_Loc);
4339    end Check_Subtype_Conformant;
4340
4341    ---------------------------
4342    -- Check_Type_Conformant --
4343    ---------------------------
4344
4345    procedure Check_Type_Conformant
4346      (New_Id  : Entity_Id;
4347       Old_Id  : Entity_Id;
4348       Err_Loc : Node_Id := Empty)
4349    is
4350       Result : Boolean;
4351    begin
4352       Check_Conformance
4353         (New_Id, Old_Id, Type_Conformant, True, Result, Err_Loc);
4354    end Check_Type_Conformant;
4355
4356    ----------------------
4357    -- Conforming_Types --
4358    ----------------------
4359
4360    function Conforming_Types
4361      (T1       : Entity_Id;
4362       T2       : Entity_Id;
4363       Ctype    : Conformance_Type;
4364       Get_Inst : Boolean := False) return Boolean
4365    is
4366       Type_1 : Entity_Id := T1;
4367       Type_2 : Entity_Id := T2;
4368       Are_Anonymous_Access_To_Subprogram_Types : Boolean := False;
4369
4370       function Base_Types_Match (T1, T2 : Entity_Id) return Boolean;
4371       --  If neither T1 nor T2 are generic actual types, or if they are in
4372       --  different scopes (e.g. parent and child instances), then verify that
4373       --  the base types are equal. Otherwise T1 and T2 must be on the same
4374       --  subtype chain. The whole purpose of this procedure is to prevent
4375       --  spurious ambiguities in an instantiation that may arise if two
4376       --  distinct generic types are instantiated with the same actual.
4377
4378       function Matches_Limited_With_View (T1, T2 : Entity_Id) return Boolean;
4379       --  Returns True if and only if either T1 denotes a limited view of T2
4380       --  or T2 denotes a limited view of T1. This can arise when the limited
4381       --  with view of a type is used in a subprogram declaration and the
4382       --  subprogram body is in the scope of a regular with clause for the
4383       --  same unit. In such a case, the two type entities can be considered
4384       --  identical for purposes of conformance checking.
4385
4386       ----------------------
4387       -- Base_Types_Match --
4388       ----------------------
4389
4390       function Base_Types_Match (T1, T2 : Entity_Id) return Boolean is
4391       begin
4392          if T1 = T2 then
4393             return True;
4394
4395          elsif Base_Type (T1) = Base_Type (T2) then
4396
4397             --  The following is too permissive. A more precise test should
4398             --  check that the generic actual is an ancestor subtype of the
4399             --  other ???.
4400
4401             return not Is_Generic_Actual_Type (T1)
4402               or else not Is_Generic_Actual_Type (T2)
4403               or else Scope (T1) /= Scope (T2);
4404
4405          else
4406             return False;
4407          end if;
4408       end Base_Types_Match;
4409
4410       -------------------------------
4411       -- Matches_Limited_With_View --
4412       -------------------------------
4413
4414       function Matches_Limited_With_View (T1, T2 : Entity_Id) return Boolean is
4415       begin
4416          --  In some cases a type imported through a limited_with clause, and
4417          --  its nonlimited view are both visible, for example in an anonymous
4418          --  access-to-class-wide type in a formal. Both entities designate the
4419          --  same type.
4420
4421          if From_With_Type (T1)
4422            and then T2 = Available_View (T1)
4423          then
4424             return True;
4425
4426          elsif From_With_Type (T2)
4427            and then T1 = Available_View (T2)
4428          then
4429             return True;
4430
4431          else
4432             return False;
4433          end if;
4434       end Matches_Limited_With_View;
4435
4436    --  Start of processing for Conforming_Types
4437
4438    begin
4439       --  The context is an instance association for a formal
4440       --  access-to-subprogram type; the formal parameter types require
4441       --  mapping because they may denote other formal parameters of the
4442       --  generic unit.
4443
4444       if Get_Inst then
4445          Type_1 := Get_Instance_Of (T1);
4446          Type_2 := Get_Instance_Of (T2);
4447       end if;
4448
4449       --  If one of the types is a view of the other introduced by a limited
4450       --  with clause, treat these as conforming for all purposes.
4451
4452       if Matches_Limited_With_View (T1, T2) then
4453          return True;
4454
4455       elsif Base_Types_Match (Type_1, Type_2) then
4456          return Ctype <= Mode_Conformant
4457            or else Subtypes_Statically_Match (Type_1, Type_2);
4458
4459       elsif Is_Incomplete_Or_Private_Type (Type_1)
4460         and then Present (Full_View (Type_1))
4461         and then Base_Types_Match (Full_View (Type_1), Type_2)
4462       then
4463          return Ctype <= Mode_Conformant
4464            or else Subtypes_Statically_Match (Full_View (Type_1), Type_2);
4465
4466       elsif Ekind (Type_2) = E_Incomplete_Type
4467         and then Present (Full_View (Type_2))
4468         and then Base_Types_Match (Type_1, Full_View (Type_2))
4469       then
4470          return Ctype <= Mode_Conformant
4471            or else Subtypes_Statically_Match (Type_1, Full_View (Type_2));
4472
4473       elsif Is_Private_Type (Type_2)
4474         and then In_Instance
4475         and then Present (Full_View (Type_2))
4476         and then Base_Types_Match (Type_1, Full_View (Type_2))
4477       then
4478          return Ctype <= Mode_Conformant
4479            or else Subtypes_Statically_Match (Type_1, Full_View (Type_2));
4480       end if;
4481
4482       --  Ada 2005 (AI-254): Anonymous access-to-subprogram types must be
4483       --  treated recursively because they carry a signature.
4484
4485       Are_Anonymous_Access_To_Subprogram_Types :=
4486         Ekind (Type_1) = Ekind (Type_2)
4487           and then
4488             (Ekind (Type_1) =  E_Anonymous_Access_Subprogram_Type
4489              or else
4490                Ekind (Type_1) = E_Anonymous_Access_Protected_Subprogram_Type);
4491
4492       --  Test anonymous access type case. For this case, static subtype
4493       --  matching is required for mode conformance (RM 6.3.1(15))
4494
4495       if (Ekind (Type_1) = E_Anonymous_Access_Type
4496             and then Ekind (Type_2) = E_Anonymous_Access_Type)
4497         or else Are_Anonymous_Access_To_Subprogram_Types -- Ada 2005 (AI-254)
4498       then
4499          declare
4500             Desig_1 : Entity_Id;
4501             Desig_2 : Entity_Id;
4502
4503          begin
4504             Desig_1 := Directly_Designated_Type (Type_1);
4505
4506             --  An access parameter can designate an incomplete type
4507             --  If the incomplete type is the limited view of a type
4508             --  from a limited_with_clause, check whether the non-limited
4509             --  view is available.
4510
4511             if Ekind (Desig_1) = E_Incomplete_Type then
4512                if Present (Full_View (Desig_1)) then
4513                   Desig_1 := Full_View (Desig_1);
4514
4515                elsif Present (Non_Limited_View (Desig_1)) then
4516                   Desig_1 := Non_Limited_View (Desig_1);
4517                end if;
4518             end if;
4519
4520             Desig_2 := Directly_Designated_Type (Type_2);
4521
4522             if Ekind (Desig_2) = E_Incomplete_Type then
4523                if Present (Full_View (Desig_2)) then
4524                   Desig_2 := Full_View (Desig_2);
4525                elsif Present (Non_Limited_View (Desig_2)) then
4526                   Desig_2 := Non_Limited_View (Desig_2);
4527                end if;
4528             end if;
4529
4530             --  The context is an instance association for a formal
4531             --  access-to-subprogram type; formal access parameter designated
4532             --  types require mapping because they may denote other formal
4533             --  parameters of the generic unit.
4534
4535             if Get_Inst then
4536                Desig_1 := Get_Instance_Of (Desig_1);
4537                Desig_2 := Get_Instance_Of (Desig_2);
4538             end if;
4539
4540             --  It is possible for a Class_Wide_Type to be introduced for an
4541             --  incomplete type, in which case there is a separate class_ wide
4542             --  type for the full view. The types conform if their Etypes
4543             --  conform, i.e. one may be the full view of the other. This can
4544             --  only happen in the context of an access parameter, other uses
4545             --  of an incomplete Class_Wide_Type are illegal.
4546
4547             if Is_Class_Wide_Type (Desig_1)
4548               and then Is_Class_Wide_Type (Desig_2)
4549             then
4550                return
4551                  Conforming_Types
4552                    (Etype (Base_Type (Desig_1)),
4553                     Etype (Base_Type (Desig_2)), Ctype);
4554
4555             elsif Are_Anonymous_Access_To_Subprogram_Types then
4556                if Ada_Version < Ada_05 then
4557                   return Ctype = Type_Conformant
4558                     or else
4559                       Subtypes_Statically_Match (Desig_1, Desig_2);
4560
4561                --  We must check the conformance of the signatures themselves
4562
4563                else
4564                   declare
4565                      Conformant : Boolean;
4566                   begin
4567                      Check_Conformance
4568                        (Desig_1, Desig_2, Ctype, False, Conformant);
4569                      return Conformant;
4570                   end;
4571                end if;
4572
4573             else
4574                return Base_Type (Desig_1) = Base_Type (Desig_2)
4575                 and then (Ctype = Type_Conformant
4576                             or else
4577                           Subtypes_Statically_Match (Desig_1, Desig_2));
4578             end if;
4579          end;
4580
4581       --  Otherwise definitely no match
4582
4583       else
4584          if ((Ekind (Type_1) = E_Anonymous_Access_Type
4585                and then Is_Access_Type (Type_2))
4586             or else (Ekind (Type_2) = E_Anonymous_Access_Type
4587                        and then Is_Access_Type (Type_1)))
4588            and then
4589              Conforming_Types
4590                (Designated_Type (Type_1), Designated_Type (Type_2), Ctype)
4591          then
4592             May_Hide_Profile := True;
4593          end if;
4594
4595          return False;
4596       end if;
4597    end Conforming_Types;
4598
4599    --------------------------
4600    -- Create_Extra_Formals --
4601    --------------------------
4602
4603    procedure Create_Extra_Formals (E : Entity_Id) is
4604       Formal      : Entity_Id;
4605       First_Extra : Entity_Id := Empty;
4606       Last_Extra  : Entity_Id;
4607       Formal_Type : Entity_Id;
4608       P_Formal    : Entity_Id := Empty;
4609
4610       function Add_Extra_Formal
4611         (Assoc_Entity : Entity_Id;
4612          Typ          : Entity_Id;
4613          Scope        : Entity_Id;
4614          Suffix       : String) return Entity_Id;
4615       --  Add an extra formal to the current list of formals and extra formals.
4616       --  The extra formal is added to the end of the list of extra formals,
4617       --  and also returned as the result. These formals are always of mode IN.
4618       --  The new formal has the type Typ, is declared in Scope, and its name
4619       --  is given by a concatenation of the name of Assoc_Entity and Suffix.
4620
4621       ----------------------
4622       -- Add_Extra_Formal --
4623       ----------------------
4624
4625       function Add_Extra_Formal
4626         (Assoc_Entity : Entity_Id;
4627          Typ          : Entity_Id;
4628          Scope        : Entity_Id;
4629          Suffix       : String) return Entity_Id
4630       is
4631          EF : constant Entity_Id :=
4632                 Make_Defining_Identifier (Sloc (Assoc_Entity),
4633                   Chars  => New_External_Name (Chars (Assoc_Entity),
4634                                                Suffix => Suffix));
4635
4636       begin
4637          --  A little optimization. Never generate an extra formal for the
4638          --  _init operand of an initialization procedure, since it could
4639          --  never be used.
4640
4641          if Chars (Formal) = Name_uInit then
4642             return Empty;
4643          end if;
4644
4645          Set_Ekind           (EF, E_In_Parameter);
4646          Set_Actual_Subtype  (EF, Typ);
4647          Set_Etype           (EF, Typ);
4648          Set_Scope           (EF, Scope);
4649          Set_Mechanism       (EF, Default_Mechanism);
4650          Set_Formal_Validity (EF);
4651
4652          if No (First_Extra) then
4653             First_Extra := EF;
4654             Set_Extra_Formals (Scope, First_Extra);
4655          end if;
4656
4657          if Present (Last_Extra) then
4658             Set_Extra_Formal (Last_Extra, EF);
4659          end if;
4660
4661          Last_Extra := EF;
4662
4663          return EF;
4664       end Add_Extra_Formal;
4665
4666    --  Start of processing for Create_Extra_Formals
4667
4668    begin
4669       --  We never generate extra formals if expansion is not active
4670       --  because we don't need them unless we are generating code.
4671
4672       if not Expander_Active then
4673          return;
4674       end if;
4675
4676       --  If this is a derived subprogram then the subtypes of the parent
4677       --  subprogram's formal parameters will be used to to determine the need
4678       --  for extra formals.
4679
4680       if Is_Overloadable (E) and then Present (Alias (E)) then
4681          P_Formal := First_Formal (Alias (E));
4682       end if;
4683
4684       Last_Extra := Empty;
4685       Formal := First_Formal (E);
4686       while Present (Formal) loop
4687          Last_Extra := Formal;
4688          Next_Formal (Formal);
4689       end loop;
4690
4691       --  If Extra_formals were already created, don't do it again. This
4692       --  situation may arise for subprogram types created as part of
4693       --  dispatching calls (see Expand_Dispatching_Call)
4694
4695       if Present (Last_Extra) and then
4696         Present (Extra_Formal (Last_Extra))
4697       then
4698          return;
4699       end if;
4700
4701       Formal := First_Formal (E);
4702
4703       while Present (Formal) loop
4704
4705          --  Create extra formal for supporting the attribute 'Constrained.
4706          --  The case of a private type view without discriminants also
4707          --  requires the extra formal if the underlying type has defaulted
4708          --  discriminants.
4709
4710          if Ekind (Formal) /= E_In_Parameter then
4711             if Present (P_Formal) then
4712                Formal_Type := Etype (P_Formal);
4713             else
4714                Formal_Type := Etype (Formal);
4715             end if;
4716
4717             --  Do not produce extra formals for Unchecked_Union parameters.
4718             --  Jump directly to the end of the loop.
4719
4720             if Is_Unchecked_Union (Base_Type (Formal_Type)) then
4721                goto Skip_Extra_Formal_Generation;
4722             end if;
4723
4724             if not Has_Discriminants (Formal_Type)
4725               and then Ekind (Formal_Type) in Private_Kind
4726               and then Present (Underlying_Type (Formal_Type))
4727             then
4728                Formal_Type := Underlying_Type (Formal_Type);
4729             end if;
4730
4731             if Has_Discriminants (Formal_Type)
4732               and then not Is_Constrained (Formal_Type)
4733               and then not Is_Indefinite_Subtype (Formal_Type)
4734             then
4735                Set_Extra_Constrained
4736                  (Formal,
4737                   Add_Extra_Formal
4738                     (Formal, Standard_Boolean, Scope (Formal), "F"));
4739             end if;
4740          end if;
4741
4742          --  Create extra formal for supporting accessibility checking. This
4743          --  is done for both anonymous access formals and formals of named
4744          --  access types that are marked as controlling formals. The latter
4745          --  case can occur when Expand_Dispatching_Call creates a subprogram
4746          --  type and substitutes the types of access-to-class-wide actuals
4747          --  for the anonymous access-to-specific-type of controlling formals.
4748
4749          --  This is suppressed if we specifically suppress accessibility
4750          --  checks at the package level for either the subprogram, or the
4751          --  package in which it resides. However, we do not suppress it
4752          --  simply if the scope has accessibility checks suppressed, since
4753          --  this could cause trouble when clients are compiled with a
4754          --  different suppression setting. The explicit checks at the
4755          --  package level are safe from this point of view.
4756
4757          if (Ekind (Etype (Formal)) = E_Anonymous_Access_Type
4758               or else (Is_Controlling_Formal (Formal)
4759                         and then Is_Access_Type (Etype (Formal))))
4760            and then not
4761              (Explicit_Suppress (E, Accessibility_Check)
4762                or else
4763               Explicit_Suppress (Scope (E), Accessibility_Check))
4764            and then
4765              (No (P_Formal)
4766                or else Present (Extra_Accessibility (P_Formal)))
4767          then
4768             --  Temporary kludge: for now we avoid creating the extra formal
4769             --  for access parameters of protected operations because of
4770             --  problem with the case of internal protected calls. ???
4771
4772             if Nkind (Parent (Parent (Parent (E)))) /= N_Protected_Definition
4773               and then Nkind (Parent (Parent (Parent (E)))) /= N_Protected_Body
4774             then
4775                Set_Extra_Accessibility
4776                  (Formal,
4777                   Add_Extra_Formal
4778                     (Formal, Standard_Natural, Scope (Formal), "F"));
4779             end if;
4780          end if;
4781
4782          --  This label is required when skipping extra formal generation for
4783          --  Unchecked_Union parameters.
4784
4785          <<Skip_Extra_Formal_Generation>>
4786
4787          if Present (P_Formal) then
4788             Next_Formal (P_Formal);
4789          end if;
4790
4791          Next_Formal (Formal);
4792       end loop;
4793
4794       --  Ada 2005 (AI-318-02): In the case of build-in-place functions, add
4795       --  appropriate extra formals. See type Exp_Ch6.BIP_Formal_Kind.
4796
4797       if Ada_Version >= Ada_05 and then Is_Build_In_Place_Function (E) then
4798          declare
4799             Result_Subt : constant Entity_Id := Etype (E);
4800
4801             Discard : Entity_Id;
4802             pragma Warnings (Off, Discard);
4803
4804          begin
4805             --  In the case of functions with unconstrained result subtypes,
4806             --  add a 3-state formal indicating whether the return object is
4807             --  allocated by the caller (0), or should be allocated by the
4808             --  callee on the secondary stack (1) or in the global heap (2).
4809             --  For the moment we just use Natural for the type of this formal.
4810             --  Note that this formal isn't usually needed in the case where
4811             --  the result subtype is constrained, but it is needed when the
4812             --  function has a tagged result, because generally such functions
4813             --  can be called in a dispatching context and such calls must be
4814             --  handled like calls to a class-wide function.
4815
4816             if not Is_Constrained (Result_Subt)
4817               or else Is_Tagged_Type (Underlying_Type (Result_Subt))
4818             then
4819                Discard :=
4820                  Add_Extra_Formal
4821                    (E, Standard_Natural,
4822                     E, BIP_Formal_Suffix (BIP_Alloc_Form));
4823             end if;
4824
4825             --  In the case of functions whose result type has controlled
4826             --  parts, we have an extra formal of type
4827             --  System.Finalization_Implementation.Finalizable_Ptr_Ptr. That
4828             --  is, we are passing a pointer to a finalization list (which is
4829             --  itself a pointer). This extra formal is then passed along to
4830             --  Move_Final_List in case of successful completion of a return
4831             --  statement. We cannot pass an 'in out' parameter, because we
4832             --  need to update the finalization list during an abort-deferred
4833             --  region, rather than using copy-back after the function
4834             --  returns. This is true even if we are able to get away with
4835             --  having 'in out' parameters, which are normally illegal for
4836             --  functions. This formal is also needed when the function has
4837             --  a tagged result, because generally such functions can be called
4838             --  in a dispatching context and such calls must be handled like
4839             --  calls to class-wide functions.
4840
4841             if Controlled_Type (Result_Subt)
4842               or else Is_Tagged_Type (Underlying_Type (Result_Subt))
4843             then
4844                Discard :=
4845                  Add_Extra_Formal
4846                    (E, RTE (RE_Finalizable_Ptr_Ptr),
4847                     E, BIP_Formal_Suffix (BIP_Final_List));
4848             end if;
4849
4850             --  If the result type contains tasks, we have two extra formals:
4851             --  the master of the tasks to be created, and the caller's
4852             --  activation chain.
4853
4854             if Has_Task (Result_Subt) then
4855                Discard :=
4856                  Add_Extra_Formal
4857                    (E, RTE (RE_Master_Id),
4858                     E, BIP_Formal_Suffix (BIP_Master));
4859                Discard :=
4860                  Add_Extra_Formal
4861                    (E, RTE (RE_Activation_Chain_Access),
4862                     E, BIP_Formal_Suffix (BIP_Activation_Chain));
4863             end if;
4864
4865             --  All build-in-place functions get an extra formal that will be
4866             --  passed the address of the return object within the caller.
4867
4868             declare
4869                Formal_Type : constant Entity_Id :=
4870                                Create_Itype
4871                                  (E_Anonymous_Access_Type, E,
4872                                   Scope_Id => Scope (E));
4873             begin
4874                Set_Directly_Designated_Type (Formal_Type, Result_Subt);
4875                Set_Etype (Formal_Type, Formal_Type);
4876                Init_Size_Align (Formal_Type);
4877                Set_Depends_On_Private
4878                  (Formal_Type, Has_Private_Component (Formal_Type));
4879                Set_Is_Public (Formal_Type, Is_Public (Scope (Formal_Type)));
4880                Set_Is_Access_Constant (Formal_Type, False);
4881
4882                --  Ada 2005 (AI-50217): Propagate the attribute that indicates
4883                --  the designated type comes from the limited view (for
4884                --  back-end purposes).
4885
4886                Set_From_With_Type (Formal_Type, From_With_Type (Result_Subt));
4887
4888                Layout_Type (Formal_Type);
4889
4890                Discard :=
4891                  Add_Extra_Formal
4892                    (E, Formal_Type, E, BIP_Formal_Suffix (BIP_Object_Access));
4893             end;
4894          end;
4895       end if;
4896    end Create_Extra_Formals;
4897
4898    -----------------------------
4899    -- Enter_Overloaded_Entity --
4900    -----------------------------
4901
4902    procedure Enter_Overloaded_Entity (S : Entity_Id) is
4903       E   : Entity_Id := Current_Entity_In_Scope (S);
4904       C_E : Entity_Id := Current_Entity (S);
4905
4906    begin
4907       if Present (E) then
4908          Set_Has_Homonym (E);
4909          Set_Has_Homonym (S);
4910       end if;
4911
4912       Set_Is_Immediately_Visible (S);
4913       Set_Scope (S, Current_Scope);
4914
4915       --  Chain new entity if front of homonym in current scope, so that
4916       --  homonyms are contiguous.
4917
4918       if Present (E)
4919         and then E /= C_E
4920       then
4921          while Homonym (C_E) /= E loop
4922             C_E := Homonym (C_E);
4923          end loop;
4924
4925          Set_Homonym (C_E, S);
4926
4927       else
4928          E := C_E;
4929          Set_Current_Entity (S);
4930       end if;
4931
4932       Set_Homonym (S, E);
4933
4934       Append_Entity (S, Current_Scope);
4935       Set_Public_Status (S);
4936
4937       if Debug_Flag_E then
4938          Write_Str ("New overloaded entity chain: ");
4939          Write_Name (Chars (S));
4940
4941          E := S;
4942          while Present (E) loop
4943             Write_Str (" "); Write_Int (Int (E));
4944             E := Homonym (E);
4945          end loop;
4946
4947          Write_Eol;
4948       end if;
4949
4950       --  Generate warning for hiding
4951
4952       if Warn_On_Hiding
4953         and then Comes_From_Source (S)
4954         and then In_Extended_Main_Source_Unit (S)
4955       then
4956          E := S;
4957          loop
4958             E := Homonym (E);
4959             exit when No (E);
4960
4961             --  Warn unless genuine overloading
4962
4963             if (not Is_Overloadable (E) or else Subtype_Conformant (E, S))
4964                   and then (Is_Immediately_Visible (E)
4965                               or else
4966                             Is_Potentially_Use_Visible (S))
4967             then
4968                Error_Msg_Sloc := Sloc (E);
4969                Error_Msg_N ("declaration of & hides one#?", S);
4970             end if;
4971          end loop;
4972       end if;
4973    end Enter_Overloaded_Entity;
4974
4975    -----------------------------
4976    -- Find_Corresponding_Spec --
4977    -----------------------------
4978
4979    function Find_Corresponding_Spec (N : Node_Id) return Entity_Id is
4980       Spec       : constant Node_Id   := Specification (N);
4981       Designator : constant Entity_Id := Defining_Entity (Spec);
4982
4983       E : Entity_Id;
4984
4985    begin
4986       E := Current_Entity (Designator);
4987
4988       while Present (E) loop
4989
4990          --  We are looking for a matching spec. It must have the same scope,
4991          --  and the same name, and either be type conformant, or be the case
4992          --  of a library procedure spec and its body (which belong to one
4993          --  another regardless of whether they are type conformant or not).
4994
4995          if Scope (E) = Current_Scope then
4996             if Current_Scope = Standard_Standard
4997               or else (Ekind (E) = Ekind (Designator)
4998                          and then Type_Conformant (E, Designator))
4999             then
5000                --  Within an instantiation, we know that spec and body are
5001                --  subtype conformant, because they were subtype conformant
5002                --  in the generic. We choose the subtype-conformant entity
5003                --  here as well, to resolve spurious ambiguities in the
5004                --  instance that were not present in the generic (i.e. when
5005                --  two different types are given the same actual). If we are
5006                --  looking for a spec to match a body, full conformance is
5007                --  expected.
5008
5009                if In_Instance then
5010                   Set_Convention (Designator, Convention (E));
5011
5012                   if Nkind (N) = N_Subprogram_Body
5013                     and then Present (Homonym (E))
5014                     and then not Fully_Conformant (E, Designator)
5015                   then
5016                      goto Next_Entity;
5017
5018                   elsif not Subtype_Conformant (E, Designator) then
5019                      goto Next_Entity;
5020                   end if;
5021                end if;
5022
5023                if not Has_Completion (E) then
5024
5025                   if Nkind (N) /= N_Subprogram_Body_Stub then
5026                      Set_Corresponding_Spec (N, E);
5027                   end if;
5028
5029                   Set_Has_Completion (E);
5030                   return E;
5031
5032                elsif Nkind (Parent (N)) = N_Subunit then
5033
5034                   --  If this is the proper body of a subunit, the completion
5035                   --  flag is set when analyzing the stub.
5036
5037                   return E;
5038
5039                --  If body already exists, this is an error unless the
5040                --  previous declaration is the implicit declaration of
5041                --  a derived subprogram, or this is a spurious overloading
5042                --  in an instance.
5043
5044                elsif No (Alias (E))
5045                  and then not Is_Intrinsic_Subprogram (E)
5046                  and then not In_Instance
5047                then
5048                   Error_Msg_Sloc := Sloc (E);
5049                   if Is_Imported (E) then
5050                      Error_Msg_NE
5051                       ("body not allowed for imported subprogram & declared#",
5052                         N, E);
5053                   else
5054                      Error_Msg_NE ("duplicate body for & declared#", N, E);
5055                   end if;
5056                end if;
5057
5058             elsif Is_Child_Unit (E)
5059               and then
5060                 Nkind (Unit_Declaration_Node (Designator)) = N_Subprogram_Body
5061               and then
5062                 Nkind (Parent (Unit_Declaration_Node (Designator)))
5063                   = N_Compilation_Unit
5064             then
5065
5066                --  Child units cannot be overloaded, so a conformance mismatch
5067                --  between body and a previous spec is an error.
5068
5069                Error_Msg_N
5070                  ("body of child unit does not match previous declaration", N);
5071             end if;
5072          end if;
5073
5074          <<Next_Entity>>
5075             E := Homonym (E);
5076       end loop;
5077
5078       --  On exit, we know that no previous declaration of subprogram exists
5079
5080       return Empty;
5081    end Find_Corresponding_Spec;
5082
5083    ----------------------
5084    -- Fully_Conformant --
5085    ----------------------
5086
5087    function Fully_Conformant (New_Id, Old_Id : Entity_Id) return Boolean is
5088       Result : Boolean;
5089    begin
5090       Check_Conformance (New_Id, Old_Id, Fully_Conformant, False, Result);
5091       return Result;
5092    end Fully_Conformant;
5093
5094    ----------------------------------
5095    -- Fully_Conformant_Expressions --
5096    ----------------------------------
5097
5098    function Fully_Conformant_Expressions
5099      (Given_E1 : Node_Id;
5100       Given_E2 : Node_Id) return Boolean
5101    is
5102       E1 : constant Node_Id := Original_Node (Given_E1);
5103       E2 : constant Node_Id := Original_Node (Given_E2);
5104       --  We always test conformance on original nodes, since it is possible
5105       --  for analysis and/or expansion to make things look as though they
5106       --  conform when they do not, e.g. by converting 1+2 into 3.
5107
5108       function FCE (Given_E1, Given_E2 : Node_Id) return Boolean
5109         renames Fully_Conformant_Expressions;
5110
5111       function FCL (L1, L2 : List_Id) return Boolean;
5112       --  Compare elements of two lists for conformance. Elements have to
5113       --  be conformant, and actuals inserted as default parameters do not
5114       --  match explicit actuals with the same value.
5115
5116       function FCO (Op_Node, Call_Node : Node_Id) return Boolean;
5117       --  Compare an operator node with a function call
5118
5119       ---------
5120       -- FCL --
5121       ---------
5122
5123       function FCL (L1, L2 : List_Id) return Boolean is
5124          N1, N2 : Node_Id;
5125
5126       begin
5127          if L1 = No_List then
5128             N1 := Empty;
5129          else
5130             N1 := First (L1);
5131          end if;
5132
5133          if L2 = No_List then
5134             N2 := Empty;
5135          else
5136             N2 := First (L2);
5137          end if;
5138
5139          --  Compare two lists, skipping rewrite insertions (we want to
5140          --  compare the original trees, not the expanded versions!)
5141
5142          loop
5143             if Is_Rewrite_Insertion (N1) then
5144                Next (N1);
5145             elsif Is_Rewrite_Insertion (N2) then
5146                Next (N2);
5147             elsif No (N1) then
5148                return No (N2);
5149             elsif No (N2) then
5150                return False;
5151             elsif not FCE (N1, N2) then
5152                return False;
5153             else
5154                Next (N1);
5155                Next (N2);
5156             end if;
5157          end loop;
5158       end FCL;
5159
5160       ---------
5161       -- FCO --
5162       ---------
5163
5164       function FCO (Op_Node, Call_Node : Node_Id) return Boolean is
5165          Actuals : constant List_Id := Parameter_Associations (Call_Node);
5166          Act     : Node_Id;
5167
5168       begin
5169          if No (Actuals)
5170             or else Entity (Op_Node) /= Entity (Name (Call_Node))
5171          then
5172             return False;
5173
5174          else
5175             Act := First (Actuals);
5176
5177             if Nkind (Op_Node) in N_Binary_Op then
5178
5179                if not FCE (Left_Opnd (Op_Node), Act) then
5180                   return False;
5181                end if;
5182
5183                Next (Act);
5184             end if;
5185
5186             return Present (Act)
5187               and then FCE (Right_Opnd (Op_Node), Act)
5188               and then No (Next (Act));
5189          end if;
5190       end FCO;
5191
5192    --  Start of processing for Fully_Conformant_Expressions
5193
5194    begin
5195       --  Non-conformant if paren count does not match. Note: if some idiot
5196       --  complains that we don't do this right for more than 3 levels of
5197       --  parentheses, they will be treated with the respect they deserve!
5198
5199       if Paren_Count (E1) /= Paren_Count (E2) then
5200          return False;
5201
5202       --  If same entities are referenced, then they are conformant even if
5203       --  they have different forms (RM 8.3.1(19-20)).
5204
5205       elsif Is_Entity_Name (E1) and then Is_Entity_Name (E2) then
5206          if Present (Entity (E1)) then
5207             return Entity (E1) = Entity (E2)
5208               or else (Chars (Entity (E1)) = Chars (Entity (E2))
5209                         and then Ekind (Entity (E1)) = E_Discriminant
5210                         and then Ekind (Entity (E2)) = E_In_Parameter);
5211
5212          elsif Nkind (E1) = N_Expanded_Name
5213            and then Nkind (E2) = N_Expanded_Name
5214            and then Nkind (Selector_Name (E1)) = N_Character_Literal
5215            and then Nkind (Selector_Name (E2)) = N_Character_Literal
5216          then
5217             return Chars (Selector_Name (E1)) = Chars (Selector_Name (E2));
5218
5219          else
5220             --  Identifiers in component associations don't always have
5221             --  entities, but their names must conform.
5222
5223             return Nkind  (E1) = N_Identifier
5224               and then Nkind (E2) = N_Identifier
5225               and then Chars (E1) = Chars (E2);
5226          end if;
5227
5228       elsif Nkind (E1) = N_Character_Literal
5229         and then Nkind (E2) = N_Expanded_Name
5230       then
5231          return Nkind (Selector_Name (E2)) = N_Character_Literal
5232            and then Chars (E1) = Chars (Selector_Name (E2));
5233
5234       elsif Nkind (E2) = N_Character_Literal
5235         and then Nkind (E1) = N_Expanded_Name
5236       then
5237          return Nkind (Selector_Name (E1)) = N_Character_Literal
5238            and then Chars (E2) = Chars (Selector_Name (E1));
5239
5240       elsif Nkind (E1) in N_Op
5241         and then Nkind (E2) = N_Function_Call
5242       then
5243          return FCO (E1, E2);
5244
5245       elsif Nkind (E2) in N_Op
5246         and then Nkind (E1) = N_Function_Call
5247       then
5248          return FCO (E2, E1);
5249
5250       --  Otherwise we must have the same syntactic entity
5251
5252       elsif Nkind (E1) /= Nkind (E2) then
5253          return False;
5254
5255       --  At this point, we specialize by node type
5256
5257       else
5258          case Nkind (E1) is
5259
5260             when N_Aggregate =>
5261                return
5262                  FCL (Expressions (E1), Expressions (E2))
5263                    and then FCL (Component_Associations (E1),
5264                                  Component_Associations (E2));
5265
5266             when N_Allocator =>
5267                if Nkind (Expression (E1)) = N_Qualified_Expression
5268                     or else
5269                   Nkind (Expression (E2)) = N_Qualified_Expression
5270                then
5271                   return FCE (Expression (E1), Expression (E2));
5272
5273                --  Check that the subtype marks and any constraints
5274                --  are conformant
5275
5276                else
5277                   declare
5278                      Indic1 : constant Node_Id := Expression (E1);
5279                      Indic2 : constant Node_Id := Expression (E2);
5280                      Elt1   : Node_Id;
5281                      Elt2   : Node_Id;
5282
5283                   begin
5284                      if Nkind (Indic1) /= N_Subtype_Indication then
5285                         return
5286                           Nkind (Indic2) /= N_Subtype_Indication
5287                             and then Entity (Indic1) = Entity (Indic2);
5288
5289                      elsif Nkind (Indic2) /= N_Subtype_Indication then
5290                         return
5291                           Nkind (Indic1) /= N_Subtype_Indication
5292                             and then Entity (Indic1) = Entity (Indic2);
5293
5294                      else
5295                         if Entity (Subtype_Mark (Indic1)) /=
5296                           Entity (Subtype_Mark (Indic2))
5297                         then
5298                            return False;
5299                         end if;
5300
5301                         Elt1 := First (Constraints (Constraint (Indic1)));
5302                         Elt2 := First (Constraints (Constraint (Indic2)));
5303
5304                         while Present (Elt1) and then Present (Elt2) loop
5305                            if not FCE (Elt1, Elt2) then
5306                               return False;
5307                            end if;
5308
5309                            Next (Elt1);
5310                            Next (Elt2);
5311                         end loop;
5312
5313                         return True;
5314                      end if;
5315                   end;
5316                end if;
5317
5318             when N_Attribute_Reference =>
5319                return
5320                  Attribute_Name (E1) = Attribute_Name (E2)
5321                    and then FCL (Expressions (E1), Expressions (E2));
5322
5323             when N_Binary_Op =>
5324                return
5325                  Entity (E1) = Entity (E2)
5326                    and then FCE (Left_Opnd  (E1), Left_Opnd  (E2))
5327                    and then FCE (Right_Opnd (E1), Right_Opnd (E2));
5328
5329             when N_And_Then | N_Or_Else | N_Membership_Test =>
5330                return
5331                  FCE (Left_Opnd  (E1), Left_Opnd  (E2))
5332                    and then
5333                  FCE (Right_Opnd (E1), Right_Opnd (E2));
5334
5335             when N_Character_Literal =>
5336                return
5337                  Char_Literal_Value (E1) = Char_Literal_Value (E2);
5338
5339             when N_Component_Association =>
5340                return
5341                  FCL (Choices (E1), Choices (E2))
5342                    and then FCE (Expression (E1), Expression (E2));
5343
5344             when N_Conditional_Expression =>
5345                return
5346                  FCL (Expressions (E1), Expressions (E2));
5347
5348             when N_Explicit_Dereference =>
5349                return
5350                  FCE (Prefix (E1), Prefix (E2));
5351
5352             when N_Extension_Aggregate =>
5353                return
5354                  FCL (Expressions (E1), Expressions (E2))
5355                    and then Null_Record_Present (E1) =
5356                             Null_Record_Present (E2)
5357                    and then FCL (Component_Associations (E1),
5358                                Component_Associations (E2));
5359
5360             when N_Function_Call =>
5361                return
5362                  FCE (Name (E1), Name (E2))
5363                    and then FCL (Parameter_Associations (E1),
5364                                  Parameter_Associations (E2));
5365
5366             when N_Indexed_Component =>
5367                return
5368                  FCE (Prefix (E1), Prefix (E2))
5369                    and then FCL (Expressions (E1), Expressions (E2));
5370
5371             when N_Integer_Literal =>
5372                return (Intval (E1) = Intval (E2));
5373
5374             when N_Null =>
5375                return True;
5376
5377             when N_Operator_Symbol =>
5378                return
5379                  Chars (E1) = Chars (E2);
5380
5381             when N_Others_Choice =>
5382                return True;
5383
5384             when N_Parameter_Association =>
5385                return
5386                  Chars (Selector_Name (E1))  = Chars (Selector_Name (E2))
5387                    and then FCE (Explicit_Actual_Parameter (E1),
5388                                  Explicit_Actual_Parameter (E2));
5389
5390             when N_Qualified_Expression =>
5391                return
5392                  FCE (Subtype_Mark (E1), Subtype_Mark (E2))
5393                    and then FCE (Expression (E1), Expression (E2));
5394
5395             when N_Range =>
5396                return
5397                  FCE (Low_Bound (E1), Low_Bound (E2))
5398                    and then FCE (High_Bound (E1), High_Bound (E2));
5399
5400             when N_Real_Literal =>
5401                return (Realval (E1) = Realval (E2));
5402
5403             when N_Selected_Component =>
5404                return
5405                  FCE (Prefix (E1), Prefix (E2))
5406                    and then FCE (Selector_Name (E1), Selector_Name (E2));
5407
5408             when N_Slice =>
5409                return
5410                  FCE (Prefix (E1), Prefix (E2))
5411                    and then FCE (Discrete_Range (E1), Discrete_Range (E2));
5412
5413             when N_String_Literal =>
5414                declare
5415                   S1 : constant String_Id := Strval (E1);
5416                   S2 : constant String_Id := Strval (E2);
5417                   L1 : constant Nat       := String_Length (S1);
5418                   L2 : constant Nat       := String_Length (S2);
5419
5420                begin
5421                   if L1 /= L2 then
5422                      return False;
5423
5424                   else
5425                      for J in 1 .. L1 loop
5426                         if Get_String_Char (S1, J) /=
5427                            Get_String_Char (S2, J)
5428                         then
5429                            return False;
5430                         end if;
5431                      end loop;
5432
5433                      return True;
5434                   end if;
5435                end;
5436
5437             when N_Type_Conversion =>
5438                return
5439                  FCE (Subtype_Mark (E1), Subtype_Mark (E2))
5440                    and then FCE (Expression (E1), Expression (E2));
5441
5442             when N_Unary_Op =>
5443                return
5444                  Entity (E1) = Entity (E2)
5445                    and then FCE (Right_Opnd (E1), Right_Opnd (E2));
5446
5447             when N_Unchecked_Type_Conversion =>
5448                return
5449                  FCE (Subtype_Mark (E1), Subtype_Mark (E2))
5450                    and then FCE (Expression (E1), Expression (E2));
5451
5452             --  All other node types cannot appear in this context. Strictly
5453             --  we should raise a fatal internal error. Instead we just ignore
5454             --  the nodes. This means that if anyone makes a mistake in the
5455             --  expander and mucks an expression tree irretrievably, the
5456             --  result will be a failure to detect a (probably very obscure)
5457             --  case of non-conformance, which is better than bombing on some
5458             --  case where two expressions do in fact conform.
5459
5460             when others =>
5461                return True;
5462
5463          end case;
5464       end if;
5465    end Fully_Conformant_Expressions;
5466
5467    ----------------------------------------
5468    -- Fully_Conformant_Discrete_Subtypes --
5469    ----------------------------------------
5470
5471    function Fully_Conformant_Discrete_Subtypes
5472      (Given_S1 : Node_Id;
5473       Given_S2 : Node_Id) return Boolean
5474    is
5475       S1 : constant Node_Id := Original_Node (Given_S1);
5476       S2 : constant Node_Id := Original_Node (Given_S2);
5477
5478       function Conforming_Bounds (B1, B2 : Node_Id) return Boolean;
5479       --  Special-case for a bound given by a discriminant, which in the body
5480       --  is replaced with the discriminal of the enclosing type.
5481
5482       function Conforming_Ranges (R1, R2 : Node_Id) return Boolean;
5483       --  Check both bounds
5484
5485       function Conforming_Bounds (B1, B2 : Node_Id) return Boolean is
5486       begin
5487          if Is_Entity_Name (B1)
5488            and then Is_Entity_Name (B2)
5489            and then Ekind (Entity (B1)) = E_Discriminant
5490          then
5491             return Chars (B1) = Chars (B2);
5492
5493          else
5494             return Fully_Conformant_Expressions (B1, B2);
5495          end if;
5496       end Conforming_Bounds;
5497
5498       function Conforming_Ranges (R1, R2 : Node_Id) return Boolean is
5499       begin
5500          return
5501            Conforming_Bounds (Low_Bound (R1), Low_Bound (R2))
5502              and then
5503            Conforming_Bounds (High_Bound (R1), High_Bound (R2));
5504       end Conforming_Ranges;
5505
5506    --  Start of processing for Fully_Conformant_Discrete_Subtypes
5507
5508    begin
5509       if Nkind (S1) /= Nkind (S2) then
5510          return False;
5511
5512       elsif Is_Entity_Name (S1) then
5513          return Entity (S1) = Entity (S2);
5514
5515       elsif Nkind (S1) = N_Range then
5516          return Conforming_Ranges (S1, S2);
5517
5518       elsif Nkind (S1) = N_Subtype_Indication then
5519          return
5520             Entity (Subtype_Mark (S1)) = Entity (Subtype_Mark (S2))
5521               and then
5522             Conforming_Ranges
5523               (Range_Expression (Constraint (S1)),
5524                Range_Expression (Constraint (S2)));
5525       else
5526          return True;
5527       end if;
5528    end Fully_Conformant_Discrete_Subtypes;
5529
5530    --------------------
5531    -- Install_Entity --
5532    --------------------
5533
5534    procedure Install_Entity (E : Entity_Id) is
5535       Prev : constant Entity_Id := Current_Entity (E);
5536    begin
5537       Set_Is_Immediately_Visible (E);
5538       Set_Current_Entity (E);
5539       Set_Homonym (E, Prev);
5540    end Install_Entity;
5541
5542    ---------------------
5543    -- Install_Formals --
5544    ---------------------
5545
5546    procedure Install_Formals (Id : Entity_Id) is
5547       F : Entity_Id;
5548    begin
5549       F := First_Formal (Id);
5550       while Present (F) loop
5551          Install_Entity (F);
5552          Next_Formal (F);
5553       end loop;
5554    end Install_Formals;
5555
5556    ---------------------------------
5557    -- Is_Non_Overriding_Operation --
5558    ---------------------------------
5559
5560    function Is_Non_Overriding_Operation
5561      (Prev_E : Entity_Id;
5562       New_E  : Entity_Id) return Boolean
5563    is
5564       Formal : Entity_Id;
5565       F_Typ  : Entity_Id;
5566       G_Typ  : Entity_Id := Empty;
5567
5568       function Get_Generic_Parent_Type (F_Typ : Entity_Id) return Entity_Id;
5569       --  If F_Type is a derived type associated with a generic actual
5570       --  subtype, then return its Generic_Parent_Type attribute, else return
5571       --  Empty.
5572
5573       function Types_Correspond
5574         (P_Type : Entity_Id;
5575          N_Type : Entity_Id) return Boolean;
5576       --  Returns true if and only if the types (or designated types in the
5577       --  case of anonymous access types) are the same or N_Type is derived
5578       --  directly or indirectly from P_Type.
5579
5580       -----------------------------
5581       -- Get_Generic_Parent_Type --
5582       -----------------------------
5583
5584       function Get_Generic_Parent_Type (F_Typ : Entity_Id) return Entity_Id is
5585          G_Typ : Entity_Id;
5586          Indic : Node_Id;
5587
5588       begin
5589          if Is_Derived_Type (F_Typ)
5590            and then Nkind (Parent (F_Typ)) = N_Full_Type_Declaration
5591          then
5592             --  The tree must be traversed to determine the parent subtype in
5593             --  the generic unit, which unfortunately isn't always available
5594             --  via semantic attributes. ??? (Note: The use of Original_Node
5595             --  is needed for cases where a full derived type has been
5596             --  rewritten.)
5597
5598             Indic := Subtype_Indication
5599                        (Type_Definition (Original_Node (Parent (F_Typ))));
5600
5601             if Nkind (Indic) = N_Subtype_Indication then
5602                G_Typ := Entity (Subtype_Mark (Indic));
5603             else
5604                G_Typ := Entity (Indic);
5605             end if;
5606
5607             if Nkind (Parent (G_Typ)) = N_Subtype_Declaration
5608               and then Present (Generic_Parent_Type (Parent (G_Typ)))
5609             then
5610                return Generic_Parent_Type (Parent (G_Typ));
5611             end if;
5612          end if;
5613
5614          return Empty;
5615       end Get_Generic_Parent_Type;
5616
5617       ----------------------
5618       -- Types_Correspond --
5619       ----------------------
5620
5621       function Types_Correspond
5622         (P_Type : Entity_Id;
5623          N_Type : Entity_Id) return Boolean
5624       is
5625          Prev_Type : Entity_Id := Base_Type (P_Type);
5626          New_Type  : Entity_Id := Base_Type (N_Type);
5627
5628       begin
5629          if Ekind (Prev_Type) = E_Anonymous_Access_Type then
5630             Prev_Type := Designated_Type (Prev_Type);
5631          end if;
5632
5633          if Ekind (New_Type) = E_Anonymous_Access_Type then
5634             New_Type := Designated_Type (New_Type);
5635          end if;
5636
5637          if Prev_Type = New_Type then
5638             return True;
5639
5640          elsif not Is_Class_Wide_Type (New_Type) then
5641             while Etype (New_Type) /= New_Type loop
5642                New_Type := Etype (New_Type);
5643                if New_Type = Prev_Type then
5644                   return True;
5645                end if;
5646             end loop;
5647          end if;
5648          return False;
5649       end Types_Correspond;
5650
5651    --  Start of processing for Is_Non_Overriding_Operation
5652
5653    begin
5654       --  In the case where both operations are implicit derived subprograms
5655       --  then neither overrides the other. This can only occur in certain
5656       --  obscure cases (e.g., derivation from homographs created in a generic
5657       --  instantiation).
5658
5659       if Present (Alias (Prev_E)) and then Present (Alias (New_E)) then
5660          return True;
5661
5662       elsif Ekind (Current_Scope) = E_Package
5663         and then Is_Generic_Instance (Current_Scope)
5664         and then In_Private_Part (Current_Scope)
5665         and then Comes_From_Source (New_E)
5666       then
5667          --  We examine the formals and result subtype of the inherited
5668          --  operation, to determine whether their type is derived from (the
5669          --  instance of) a generic type.
5670
5671          Formal := First_Formal (Prev_E);
5672
5673          while Present (Formal) loop
5674             F_Typ := Base_Type (Etype (Formal));
5675
5676             if Ekind (F_Typ) = E_Anonymous_Access_Type then
5677                F_Typ := Designated_Type (F_Typ);
5678             end if;
5679
5680             G_Typ := Get_Generic_Parent_Type (F_Typ);
5681
5682             Next_Formal (Formal);
5683          end loop;
5684
5685          if No (G_Typ) and then Ekind (Prev_E) = E_Function then
5686             G_Typ := Get_Generic_Parent_Type (Base_Type (Etype (Prev_E)));
5687          end if;
5688
5689          if No (G_Typ) then
5690             return False;
5691          end if;
5692
5693          --  If the generic type is a private type, then the original
5694          --  operation was not overriding in the generic, because there was
5695          --  no primitive operation to override.
5696
5697          if Nkind (Parent (G_Typ)) = N_Formal_Type_Declaration
5698            and then Nkind (Formal_Type_Definition (Parent (G_Typ))) =
5699              N_Formal_Private_Type_Definition
5700          then
5701             return True;
5702
5703          --  The generic parent type is the ancestor of a formal derived
5704          --  type declaration. We need to check whether it has a primitive
5705          --  operation that should be overridden by New_E in the generic.
5706
5707          else
5708             declare
5709                P_Formal : Entity_Id;
5710                N_Formal : Entity_Id;
5711                P_Typ    : Entity_Id;
5712                N_Typ    : Entity_Id;
5713                P_Prim   : Entity_Id;
5714                Prim_Elt : Elmt_Id := First_Elmt (Primitive_Operations (G_Typ));
5715
5716             begin
5717                while Present (Prim_Elt) loop
5718                   P_Prim := Node (Prim_Elt);
5719
5720                   if Chars (P_Prim) = Chars (New_E)
5721                     and then Ekind (P_Prim) = Ekind (New_E)
5722                   then
5723                      P_Formal := First_Formal (P_Prim);
5724                      N_Formal := First_Formal (New_E);
5725                      while Present (P_Formal) and then Present (N_Formal) loop
5726                         P_Typ := Etype (P_Formal);
5727                         N_Typ := Etype (N_Formal);
5728
5729                         if not Types_Correspond (P_Typ, N_Typ) then
5730                            exit;
5731                         end if;
5732
5733                         Next_Entity (P_Formal);
5734                         Next_Entity (N_Formal);
5735                      end loop;
5736
5737                      --  Found a matching primitive operation belonging to the
5738                      --  formal ancestor type, so the new subprogram is
5739                      --  overriding.
5740
5741                      if No (P_Formal)
5742                        and then No (N_Formal)
5743                        and then (Ekind (New_E) /= E_Function
5744                                   or else
5745                                  Types_Correspond
5746                                    (Etype (P_Prim), Etype (New_E)))
5747                      then
5748                         return False;
5749                      end if;
5750                   end if;
5751
5752                   Next_Elmt (Prim_Elt);
5753                end loop;
5754
5755                --  If no match found, then the new subprogram does not
5756                --  override in the generic (nor in the instance).
5757
5758                return True;
5759             end;
5760          end if;
5761       else
5762          return False;
5763       end if;
5764    end Is_Non_Overriding_Operation;
5765
5766    ------------------------------
5767    -- Make_Inequality_Operator --
5768    ------------------------------
5769
5770    --  S is the defining identifier of an equality operator. We build a
5771    --  subprogram declaration with the right signature. This operation is
5772    --  intrinsic, because it is always expanded as the negation of the
5773    --  call to the equality function.
5774
5775    procedure Make_Inequality_Operator (S : Entity_Id) is
5776       Loc     : constant Source_Ptr := Sloc (S);
5777       Decl    : Node_Id;
5778       Formals : List_Id;
5779       Op_Name : Entity_Id;
5780
5781       FF : constant Entity_Id := First_Formal (S);
5782       NF : constant Entity_Id := Next_Formal (FF);
5783
5784    begin
5785       --  Check that equality was properly defined, ignore call if not
5786
5787       if No (NF) then
5788          return;
5789       end if;
5790
5791       declare
5792          A : constant Entity_Id :=
5793                Make_Defining_Identifier (Sloc (FF),
5794                  Chars => Chars (FF));
5795
5796          B  : constant Entity_Id :=
5797                 Make_Defining_Identifier (Sloc (NF),
5798                   Chars => Chars (NF));
5799
5800       begin
5801          Op_Name := Make_Defining_Operator_Symbol (Loc, Name_Op_Ne);
5802
5803          Formals := New_List (
5804            Make_Parameter_Specification (Loc,
5805              Defining_Identifier => A,
5806              Parameter_Type      =>
5807                New_Reference_To (Etype (First_Formal (S)),
5808                  Sloc (Etype (First_Formal (S))))),
5809
5810            Make_Parameter_Specification (Loc,
5811              Defining_Identifier => B,
5812              Parameter_Type      =>
5813                New_Reference_To (Etype (Next_Formal (First_Formal (S))),
5814                  Sloc (Etype (Next_Formal (First_Formal (S)))))));
5815
5816          Decl :=
5817            Make_Subprogram_Declaration (Loc,
5818              Specification =>
5819                Make_Function_Specification (Loc,
5820                  Defining_Unit_Name       => Op_Name,
5821                  Parameter_Specifications => Formals,
5822                  Result_Definition        =>
5823                    New_Reference_To (Standard_Boolean, Loc)));
5824
5825          --  Insert inequality right after equality if it is explicit or after
5826          --  the derived type when implicit. These entities are created only
5827          --  for visibility purposes, and eventually replaced in the course of
5828          --  expansion, so they do not need to be attached to the tree and seen
5829          --  by the back-end. Keeping them internal also avoids spurious
5830          --  freezing problems. The declaration is inserted in the tree for
5831          --  analysis, and removed afterwards. If the equality operator comes
5832          --  from an explicit declaration, attach the inequality immediately
5833          --  after. Else the equality is inherited from a derived type
5834          --  declaration, so insert inequality after that declaration.
5835
5836          if No (Alias (S)) then
5837             Insert_After (Unit_Declaration_Node (S), Decl);
5838          elsif Is_List_Member (Parent (S)) then
5839             Insert_After (Parent (S), Decl);
5840          else
5841             Insert_After (Parent (Etype (First_Formal (S))), Decl);
5842          end if;
5843
5844          Mark_Rewrite_Insertion (Decl);
5845          Set_Is_Intrinsic_Subprogram (Op_Name);
5846          Analyze (Decl);
5847          Remove (Decl);
5848          Set_Has_Completion (Op_Name);
5849          Set_Corresponding_Equality (Op_Name, S);
5850          Set_Is_Abstract_Subprogram (Op_Name, Is_Abstract_Subprogram (S));
5851       end;
5852    end Make_Inequality_Operator;
5853
5854    ----------------------
5855    -- May_Need_Actuals --
5856    ----------------------
5857
5858    procedure May_Need_Actuals (Fun : Entity_Id) is
5859       F : Entity_Id;
5860       B : Boolean;
5861
5862    begin
5863       F := First_Formal (Fun);
5864       B := True;
5865
5866       while Present (F) loop
5867          if No (Default_Value (F)) then
5868             B := False;
5869             exit;
5870          end if;
5871
5872          Next_Formal (F);
5873       end loop;
5874
5875       Set_Needs_No_Actuals (Fun, B);
5876    end May_Need_Actuals;
5877
5878    ---------------------
5879    -- Mode_Conformant --
5880    ---------------------
5881
5882    function Mode_Conformant (New_Id, Old_Id : Entity_Id) return Boolean is
5883       Result : Boolean;
5884    begin
5885       Check_Conformance (New_Id, Old_Id, Mode_Conformant, False, Result);
5886       return Result;
5887    end Mode_Conformant;
5888
5889    ---------------------------
5890    -- New_Overloaded_Entity --
5891    ---------------------------
5892
5893    procedure New_Overloaded_Entity
5894      (S            : Entity_Id;
5895       Derived_Type : Entity_Id := Empty)
5896    is
5897       Overridden_Subp : Entity_Id := Empty;
5898       --  Set if the current scope has an operation that is type-conformant
5899       --  with S, and becomes hidden by S.
5900
5901       E : Entity_Id;
5902       --  Entity that S overrides
5903
5904       Prev_Vis : Entity_Id := Empty;
5905       --  Predecessor of E in Homonym chain
5906
5907       procedure Check_Synchronized_Overriding
5908         (Def_Id          : Entity_Id;
5909          First_Hom       : Entity_Id;
5910          Overridden_Subp : out Entity_Id);
5911       --  First determine if Def_Id is an entry or a subprogram either defined
5912       --  in the scope of a task or protected type, or is a primitive of such
5913       --  a type. Check whether Def_Id overrides a subprogram of an interface
5914       --  implemented by the synchronized type, return the overridden entity
5915       --  or Empty.
5916
5917       function Is_Private_Declaration (E : Entity_Id) return Boolean;
5918       --  Check that E is declared in the private part of the current package,
5919       --  or in the package body, where it may hide a previous declaration.
5920       --  We can't use In_Private_Part by itself because this flag is also
5921       --  set when freezing entities, so we must examine the place of the
5922       --  declaration in the tree, and recognize wrapper packages as well.
5923
5924       procedure Maybe_Primitive_Operation (Is_Overriding : Boolean := False);
5925       --  If the subprogram being analyzed is a primitive operation of
5926       --  the type of one of its formals, set the corresponding flag.
5927
5928       -----------------------------------
5929       -- Check_Synchronized_Overriding --
5930       -----------------------------------
5931
5932       procedure Check_Synchronized_Overriding
5933         (Def_Id          : Entity_Id;
5934          First_Hom       : Entity_Id;
5935          Overridden_Subp : out Entity_Id)
5936       is
5937          Formal_Typ  : Entity_Id;
5938          Ifaces_List : Elist_Id;
5939          In_Scope    : Boolean;
5940          Typ         : Entity_Id;
5941
5942       begin
5943          Overridden_Subp := Empty;
5944
5945          --  Def_Id must be an entry or a subprogram
5946
5947          if Ekind (Def_Id) /= E_Entry
5948            and then Ekind (Def_Id) /= E_Function
5949            and then Ekind (Def_Id) /= E_Procedure
5950          then
5951             return;
5952          end if;
5953
5954          --  Search for the concurrent declaration since it contains the list
5955          --  of all implemented interfaces. In this case, the subprogram is
5956          --  declared within the scope of a protected or a task type.
5957
5958          if Present (Scope (Def_Id))
5959            and then Is_Concurrent_Type (Scope (Def_Id))
5960            and then not Is_Generic_Actual_Type (Scope (Def_Id))
5961          then
5962             Typ := Scope (Def_Id);
5963             In_Scope := True;
5964
5965          --  The subprogram may be a primitive of a concurrent type
5966
5967          elsif Present (First_Formal (Def_Id)) then
5968             Formal_Typ := Etype (First_Formal (Def_Id));
5969
5970             if Is_Concurrent_Type (Formal_Typ)
5971               and then not Is_Generic_Actual_Type (Formal_Typ)
5972             then
5973                Typ := Formal_Typ;
5974                In_Scope := False;
5975
5976             --  This case occurs when the concurrent type is declared within
5977             --  a generic unit. As a result the corresponding record has been
5978             --  built and used as the type of the first formal, we just have
5979             --  to retrieve the corresponding concurrent type.
5980
5981             elsif Is_Concurrent_Record_Type (Formal_Typ)
5982               and then Present (Corresponding_Concurrent_Type (Formal_Typ))
5983             then
5984                Typ := Corresponding_Concurrent_Type (Formal_Typ);
5985                In_Scope := False;
5986
5987             else
5988                return;
5989             end if;
5990          else
5991             return;
5992          end if;
5993
5994          --  Gather all limited, protected and task interfaces that Typ
5995          --  implements. There is no overriding to check if is an inherited
5996          --  operation in a type derivation on for a generic actual.
5997
5998          if Nkind (Parent (Typ)) /= N_Full_Type_Declaration
5999            and then Nkind (Parent (Def_Id)) /= N_Subtype_Declaration
6000            and then Nkind (Parent (Def_Id)) /= N_Task_Type_Declaration
6001            and then Nkind (Parent (Def_Id)) /= N_Protected_Type_Declaration
6002          then
6003             Collect_Abstract_Interfaces (Typ, Ifaces_List);
6004
6005             if not Is_Empty_Elmt_List (Ifaces_List) then
6006                Overridden_Subp :=
6007                  Find_Overridden_Synchronized_Primitive
6008                    (Def_Id, First_Hom, Ifaces_List, In_Scope);
6009             end if;
6010          end if;
6011       end Check_Synchronized_Overriding;
6012
6013       ----------------------------
6014       -- Is_Private_Declaration --
6015       ----------------------------
6016
6017       function Is_Private_Declaration (E : Entity_Id) return Boolean is
6018          Priv_Decls : List_Id;
6019          Decl       : constant Node_Id := Unit_Declaration_Node (E);
6020
6021       begin
6022          if Is_Package_Or_Generic_Package (Current_Scope)
6023            and then In_Private_Part (Current_Scope)
6024          then
6025             Priv_Decls :=
6026               Private_Declarations (
6027                 Specification (Unit_Declaration_Node (Current_Scope)));
6028
6029             return In_Package_Body (Current_Scope)
6030               or else
6031                 (Is_List_Member (Decl)
6032                    and then List_Containing (Decl) = Priv_Decls)
6033               or else (Nkind (Parent (Decl)) = N_Package_Specification
6034                          and then not Is_Compilation_Unit (
6035                            Defining_Entity (Parent (Decl)))
6036                          and then List_Containing (Parent (Parent (Decl)))
6037                            = Priv_Decls);
6038          else
6039             return False;
6040          end if;
6041       end Is_Private_Declaration;
6042
6043       -------------------------------
6044       -- Maybe_Primitive_Operation --
6045       -------------------------------
6046
6047       procedure Maybe_Primitive_Operation (Is_Overriding : Boolean := False) is
6048          Formal : Entity_Id;
6049          F_Typ  : Entity_Id;
6050          B_Typ  : Entity_Id;
6051
6052          function Visible_Part_Type (T : Entity_Id) return Boolean;
6053          --  Returns true if T is declared in the visible part of
6054          --  the current package scope; otherwise returns false.
6055          --  Assumes that T is declared in a package.
6056
6057          procedure Check_Private_Overriding (T : Entity_Id);
6058          --  Checks that if a primitive abstract subprogram of a visible
6059          --  abstract type is declared in a private part, then it must
6060          --  override an abstract subprogram declared in the visible part.
6061          --  Also checks that if a primitive function with a controlling
6062          --  result is declared in a private part, then it must override
6063          --  a function declared in the visible part.
6064
6065          ------------------------------
6066          -- Check_Private_Overriding --
6067          ------------------------------
6068
6069          procedure Check_Private_Overriding (T : Entity_Id) is
6070          begin
6071             if Ekind (Current_Scope) = E_Package
6072               and then In_Private_Part (Current_Scope)
6073               and then Visible_Part_Type (T)
6074               and then not In_Instance
6075             then
6076                if Is_Abstract_Type (T)
6077                  and then Is_Abstract_Subprogram (S)
6078                  and then (not Is_Overriding
6079                            or else not Is_Abstract_Subprogram (E))
6080                then
6081                   Error_Msg_N ("abstract subprograms must be visible "
6082                                    & "('R'M 3.9.3(10))!", S);
6083
6084                elsif Ekind (S) = E_Function
6085                  and then Is_Tagged_Type (T)
6086                  and then T = Base_Type (Etype (S))
6087                  and then not Is_Overriding
6088                then
6089                   Error_Msg_N
6090                     ("private function with tagged result must"
6091                      & " override visible-part function", S);
6092                   Error_Msg_N
6093                     ("\move subprogram to the visible part"
6094                      & " ('R'M 3.9.3(10))", S);
6095                end if;
6096             end if;
6097          end Check_Private_Overriding;
6098
6099          -----------------------
6100          -- Visible_Part_Type --
6101          -----------------------
6102
6103          function Visible_Part_Type (T : Entity_Id) return Boolean is
6104             P : constant Node_Id := Unit_Declaration_Node (Scope (T));
6105             N : Node_Id;
6106
6107          begin
6108             --  If the entity is a private type, then it must be
6109             --  declared in a visible part.
6110
6111             if Ekind (T) in Private_Kind then
6112                return True;
6113             end if;
6114
6115             --  Otherwise, we traverse the visible part looking for its
6116             --  corresponding declaration. We cannot use the declaration
6117             --  node directly because in the private part the entity of a
6118             --  private type is the one in the full view, which does not
6119             --  indicate that it is the completion of something visible.
6120
6121             N := First (Visible_Declarations (Specification (P)));
6122             while Present (N) loop
6123                if Nkind (N) = N_Full_Type_Declaration
6124                  and then Present (Defining_Identifier (N))
6125                  and then T = Defining_Identifier (N)
6126                then
6127                   return True;
6128
6129                elsif (Nkind (N) = N_Private_Type_Declaration
6130                        or else
6131                       Nkind (N) = N_Private_Extension_Declaration)
6132                  and then Present (Defining_Identifier (N))
6133                  and then T = Full_View (Defining_Identifier (N))
6134                then
6135                   return True;
6136                end if;
6137
6138                Next (N);
6139             end loop;
6140
6141             return False;
6142          end Visible_Part_Type;
6143
6144       --  Start of processing for Maybe_Primitive_Operation
6145
6146       begin
6147          if not Comes_From_Source (S) then
6148             null;
6149
6150          --  If the subprogram is at library level, it is not primitive
6151          --  operation.
6152
6153          elsif Current_Scope = Standard_Standard then
6154             null;
6155
6156          elsif (Ekind (Current_Scope) = E_Package
6157                  and then not In_Package_Body (Current_Scope))
6158            or else Is_Overriding
6159          then
6160             --  For function, check return type
6161
6162             if Ekind (S) = E_Function then
6163                B_Typ := Base_Type (Etype (S));
6164
6165                if Scope (B_Typ) = Current_Scope then
6166                   Set_Has_Primitive_Operations (B_Typ);
6167                   Check_Private_Overriding (B_Typ);
6168                end if;
6169             end if;
6170
6171             --  For all subprograms, check formals
6172
6173             Formal := First_Formal (S);
6174             while Present (Formal) loop
6175                if Ekind (Etype (Formal)) = E_Anonymous_Access_Type then
6176                   F_Typ := Designated_Type (Etype (Formal));
6177                else
6178                   F_Typ := Etype (Formal);
6179                end if;
6180
6181                B_Typ := Base_Type (F_Typ);
6182
6183                if Ekind (B_Typ) = E_Access_Subtype then
6184                   B_Typ := Base_Type (B_Typ);
6185                end if;
6186
6187                if Scope (B_Typ) = Current_Scope then
6188                   Set_Has_Primitive_Operations (B_Typ);
6189                   Check_Private_Overriding (B_Typ);
6190                end if;
6191
6192                Next_Formal (Formal);
6193             end loop;
6194          end if;
6195       end Maybe_Primitive_Operation;
6196
6197    --  Start of processing for New_Overloaded_Entity
6198
6199    begin
6200       --  We need to look for an entity that S may override. This must be a
6201       --  homonym in the current scope, so we look for the first homonym of
6202       --  S in the current scope as the starting point for the search.
6203
6204       E := Current_Entity_In_Scope (S);
6205
6206       --  If there is no homonym then this is definitely not overriding
6207
6208       if No (E) then
6209          Enter_Overloaded_Entity (S);
6210          Check_Dispatching_Operation (S, Empty);
6211          Maybe_Primitive_Operation;
6212
6213          --  If subprogram has an explicit declaration, check whether it
6214          --  has an overriding indicator.
6215
6216          if Comes_From_Source (S) then
6217             Check_Synchronized_Overriding (S, Homonym (S), Overridden_Subp);
6218             Check_Overriding_Indicator (S, Overridden_Subp);
6219          end if;
6220
6221       --  If there is a homonym that is not overloadable, then we have an
6222       --  error, except for the special cases checked explicitly below.
6223
6224       elsif not Is_Overloadable (E) then
6225
6226          --  Check for spurious conflict produced by a subprogram that has the
6227          --  same name as that of the enclosing generic package. The conflict
6228          --  occurs within an instance, between the subprogram and the renaming
6229          --  declaration for the package. After the subprogram, the package
6230          --  renaming declaration becomes hidden.
6231
6232          if Ekind (E) = E_Package
6233            and then Present (Renamed_Object (E))
6234            and then Renamed_Object (E) = Current_Scope
6235            and then Nkind (Parent (Renamed_Object (E))) =
6236                                                      N_Package_Specification
6237            and then Present (Generic_Parent (Parent (Renamed_Object (E))))
6238          then
6239             Set_Is_Hidden (E);
6240             Set_Is_Immediately_Visible (E, False);
6241             Enter_Overloaded_Entity (S);
6242             Set_Homonym (S, Homonym (E));
6243             Check_Dispatching_Operation (S, Empty);
6244             Check_Overriding_Indicator (S, Empty);
6245
6246          --  If the subprogram is implicit it is hidden by the previous
6247          --  declaration. However if it is dispatching, it must appear in the
6248          --  dispatch table anyway, because it can be dispatched to even if it
6249          --  cannot be called directly.
6250
6251          elsif Present (Alias (S))
6252            and then not Comes_From_Source (S)
6253          then
6254             Set_Scope (S, Current_Scope);
6255
6256             if Is_Dispatching_Operation (Alias (S)) then
6257                Check_Dispatching_Operation (S, Empty);
6258             end if;
6259
6260             return;
6261
6262          else
6263             Error_Msg_Sloc := Sloc (E);
6264             Error_Msg_N ("& conflicts with declaration#", S);
6265
6266             --  Useful additional warning
6267
6268             if Is_Generic_Unit (E) then
6269                Error_Msg_N ("\previous generic unit cannot be overloaded", S);
6270             end if;
6271
6272             return;
6273          end if;
6274
6275       --  E exists and is overloadable
6276
6277       else
6278          --  Ada 2005 (AI-251): Derivation of abstract interface primitives
6279          --  need no check against the homonym chain. They are directly added
6280          --  to the list of primitive operations of Derived_Type.
6281
6282          if Ada_Version >= Ada_05
6283            and then Present (Derived_Type)
6284            and then Is_Dispatching_Operation (Alias (S))
6285            and then Present (Find_Dispatching_Type (Alias (S)))
6286            and then Is_Interface (Find_Dispatching_Type (Alias (S)))
6287            and then not Is_Predefined_Dispatching_Operation (Alias (S))
6288          then
6289             goto Add_New_Entity;
6290          end if;
6291
6292          Check_Synchronized_Overriding (S, E, Overridden_Subp);
6293
6294          --  Loop through E and its homonyms to determine if any of them is
6295          --  the candidate for overriding by S.
6296
6297          while Present (E) loop
6298
6299             --  Definitely not interesting if not in the current scope
6300
6301             if Scope (E) /= Current_Scope then
6302                null;
6303
6304             --  Check if we have type conformance
6305
6306             elsif Type_Conformant (E, S) then
6307
6308                --  If the old and new entities have the same profile and one
6309                --  is not the body of the other, then this is an error, unless
6310                --  one of them is implicitly declared.
6311
6312                --  There are some cases when both can be implicit, for example
6313                --  when both a literal and a function that overrides it are
6314                --  inherited in a derivation, or when an inhertited operation
6315                --  of a tagged full type overrides the inherited operation of
6316                --  a private extension. Ada 83 had a special rule for the the
6317                --  literal case. In Ada95, the later implicit operation hides
6318                --  the former, and the literal is always the former. In the
6319                --  odd case where both are derived operations declared at the
6320                --  same point, both operations should be declared, and in that
6321                --  case we bypass the following test and proceed to the next
6322                --  part (this can only occur for certain obscure cases
6323                --  involving homographs in instances and can't occur for
6324                --  dispatching operations ???). Note that the following
6325                --  condition is less than clear. For example, it's not at all
6326                --  clear why there's a test for E_Entry here. ???
6327
6328                if Present (Alias (S))
6329                  and then (No (Alias (E))
6330                             or else Comes_From_Source (E)
6331                             or else Is_Dispatching_Operation (E))
6332                  and then
6333                    (Ekind (E) = E_Entry
6334                      or else Ekind (E) /= E_Enumeration_Literal)
6335                then
6336                   --  When an derived operation is overloaded it may be due to
6337                   --  the fact that the full view of a private extension
6338                   --  re-inherits. It has to be dealt with.
6339
6340                   if Is_Package_Or_Generic_Package (Current_Scope)
6341                     and then In_Private_Part (Current_Scope)
6342                   then
6343                      Check_Operation_From_Private_View (S, E);
6344                   end if;
6345
6346                   --  In any case the implicit operation remains hidden by
6347                   --  the existing declaration, which is overriding.
6348
6349                   Set_Is_Overriding_Operation (E);
6350
6351                   if Comes_From_Source (E) then
6352                      Check_Overriding_Indicator (E, S);
6353
6354                      --  Indicate that E overrides the operation from which
6355                      --  S is inherited.
6356
6357                      if Present (Alias (S)) then
6358                         Set_Overridden_Operation (E, Alias (S));
6359                      else
6360                         Set_Overridden_Operation (E, S);
6361                      end if;
6362                   end if;
6363
6364                   return;
6365
6366                   --  Within an instance, the renaming declarations for
6367                   --  actual subprograms may become ambiguous, but they do
6368                   --  not hide each other.
6369
6370                elsif Ekind (E) /= E_Entry
6371                  and then not Comes_From_Source (E)
6372                  and then not Is_Generic_Instance (E)
6373                  and then (Present (Alias (E))
6374                             or else Is_Intrinsic_Subprogram (E))
6375                  and then (not In_Instance
6376                             or else No (Parent (E))
6377                             or else Nkind (Unit_Declaration_Node (E)) /=
6378                                N_Subprogram_Renaming_Declaration)
6379                then
6380                   --  A subprogram child unit is not allowed to override
6381                   --  an inherited subprogram (10.1.1(20)).
6382
6383                   if Is_Child_Unit (S) then
6384                      Error_Msg_N
6385                        ("child unit overrides inherited subprogram in parent",
6386                         S);
6387                      return;
6388                   end if;
6389
6390                   if Is_Non_Overriding_Operation (E, S) then
6391                      Enter_Overloaded_Entity (S);
6392                      if No (Derived_Type)
6393                        or else Is_Tagged_Type (Derived_Type)
6394                      then
6395                         Check_Dispatching_Operation (S, Empty);
6396                      end if;
6397
6398                      return;
6399                   end if;
6400
6401                   --  E is a derived operation or an internal operator which
6402                   --  is being overridden. Remove E from further visibility.
6403                   --  Furthermore, if E is a dispatching operation, it must be
6404                   --  replaced in the list of primitive operations of its type
6405                   --  (see Override_Dispatching_Operation).
6406
6407                   Overridden_Subp := E;
6408
6409                   declare
6410                      Prev : Entity_Id;
6411
6412                   begin
6413                      Prev := First_Entity (Current_Scope);
6414
6415                      while Present (Prev)
6416                        and then Next_Entity (Prev) /= E
6417                      loop
6418                         Next_Entity (Prev);
6419                      end loop;
6420
6421                      --  It is possible for E to be in the current scope and
6422                      --  yet not in the entity chain. This can only occur in a
6423                      --  generic context where E is an implicit concatenation
6424                      --  in the formal part, because in a generic body the
6425                      --  entity chain starts with the formals.
6426
6427                      pragma Assert
6428                        (Present (Prev) or else Chars (E) = Name_Op_Concat);
6429
6430                      --  E must be removed both from the entity_list of the
6431                      --  current scope, and from the visibility chain
6432
6433                      if Debug_Flag_E then
6434                         Write_Str ("Override implicit operation ");
6435                         Write_Int (Int (E));
6436                         Write_Eol;
6437                      end if;
6438
6439                      --  If E is a predefined concatenation, it stands for four
6440                      --  different operations. As a result, a single explicit
6441                      --  declaration does not hide it. In a possible ambiguous
6442                      --  situation, Disambiguate chooses the user-defined op,
6443                      --  so it is correct to retain the previous internal one.
6444
6445                      if Chars (E) /= Name_Op_Concat
6446                        or else Ekind (E) /= E_Operator
6447                      then
6448                         --  For nondispatching derived operations that are
6449                         --  overridden by a subprogram declared in the private
6450                         --  part of a package, we retain the derived
6451                         --  subprogram but mark it as not immediately visible.
6452                         --  If the derived operation was declared in the
6453                         --  visible part then this ensures that it will still
6454                         --  be visible outside the package with the proper
6455                         --  signature (calls from outside must also be
6456                         --  directed to this version rather than the
6457                         --  overriding one, unlike the dispatching case).
6458                         --  Calls from inside the package will still resolve
6459                         --  to the overriding subprogram since the derived one
6460                         --  is marked as not visible within the package.
6461
6462                         --  If the private operation is dispatching, we achieve
6463                         --  the overriding by keeping the implicit operation
6464                         --  but setting its alias to be the overriding one. In
6465                         --  this fashion the proper body is executed in all
6466                         --  cases, but the original signature is used outside
6467                         --  of the package.
6468
6469                         --  If the overriding is not in the private part, we
6470                         --  remove the implicit operation altogether.
6471
6472                         if Is_Private_Declaration (S) then
6473
6474                            if not Is_Dispatching_Operation (E) then
6475                               Set_Is_Immediately_Visible (E, False);
6476                            else
6477                               --  Work done in Override_Dispatching_Operation,
6478                               --  so nothing else need to be done here.
6479
6480                               null;
6481                            end if;
6482
6483                         else
6484                            --  Find predecessor of E in Homonym chain
6485
6486                            if E = Current_Entity (E) then
6487                               Prev_Vis := Empty;
6488                            else
6489                               Prev_Vis := Current_Entity (E);
6490                               while Homonym (Prev_Vis) /= E loop
6491                                  Prev_Vis := Homonym (Prev_Vis);
6492                               end loop;
6493                            end if;
6494
6495                            if Prev_Vis /= Empty then
6496
6497                               --  Skip E in the visibility chain
6498
6499                               Set_Homonym (Prev_Vis, Homonym (E));
6500
6501                            else
6502                               Set_Name_Entity_Id (Chars (E), Homonym (E));
6503                            end if;
6504
6505                            Set_Next_Entity (Prev, Next_Entity (E));
6506
6507                            if No (Next_Entity (Prev)) then
6508                               Set_Last_Entity (Current_Scope, Prev);
6509                            end if;
6510
6511                         end if;
6512                      end if;
6513
6514                      Enter_Overloaded_Entity (S);
6515                      Set_Is_Overriding_Operation (S);
6516                      Check_Overriding_Indicator (S, E);
6517
6518                      --  Indicate that S overrides the operation from which
6519                      --  E is inherited.
6520
6521                      if Comes_From_Source (S) then
6522                         if Present (Alias (E)) then
6523                            Set_Overridden_Operation (S, Alias (E));
6524                         else
6525                            Set_Overridden_Operation (S, E);
6526                         end if;
6527                      end if;
6528
6529                      if Is_Dispatching_Operation (E) then
6530
6531                         --  An overriding dispatching subprogram inherits the
6532                         --  convention of the overridden subprogram (by
6533                         --  AI-117).
6534
6535                         Set_Convention (S, Convention (E));
6536                         Check_Dispatching_Operation (S, E);
6537
6538                      else
6539                         Check_Dispatching_Operation (S, Empty);
6540                      end if;
6541
6542                      Maybe_Primitive_Operation (Is_Overriding => True);
6543                      goto Check_Inequality;
6544                   end;
6545
6546                --  Apparent redeclarations in instances can occur when two
6547                --  formal types get the same actual type. The subprograms in
6548                --  in the instance are legal,  even if not callable from the
6549                --  outside. Calls from within are disambiguated elsewhere.
6550                --  For dispatching operations in the visible part, the usual
6551                --  rules apply, and operations with the same profile are not
6552                --  legal (B830001).
6553
6554                elsif (In_Instance_Visible_Part
6555                        and then not Is_Dispatching_Operation (E))
6556                  or else In_Instance_Not_Visible
6557                then
6558                   null;
6559
6560                --  Here we have a real error (identical profile)
6561
6562                else
6563                   Error_Msg_Sloc := Sloc (E);
6564
6565                   --  Avoid cascaded errors if the entity appears in
6566                   --  subsequent calls.
6567
6568                   Set_Scope (S, Current_Scope);
6569
6570                   Error_Msg_N ("& conflicts with declaration#", S);
6571
6572                   if Is_Generic_Instance (S)
6573                     and then not Has_Completion (E)
6574                   then
6575                      Error_Msg_N
6576                        ("\instantiation cannot provide body for it", S);
6577                   end if;
6578
6579                   return;
6580                end if;
6581
6582             else
6583                --  If one subprogram has an access parameter and the other
6584                --  a parameter of an access type, calls to either might be
6585                --  ambiguous. Verify that parameters match except for the
6586                --  access parameter.
6587
6588                if May_Hide_Profile then
6589                   declare
6590                      F1 : Entity_Id;
6591                      F2 : Entity_Id;
6592                   begin
6593                      F1 := First_Formal (S);
6594                      F2 := First_Formal (E);
6595                      while Present (F1) and then Present (F2) loop
6596                         if Is_Access_Type (Etype (F1)) then
6597                            if not Is_Access_Type (Etype (F2))
6598                               or else not Conforming_Types
6599                                 (Designated_Type (Etype (F1)),
6600                                  Designated_Type (Etype (F2)),
6601                                  Type_Conformant)
6602                            then
6603                               May_Hide_Profile := False;
6604                            end if;
6605
6606                         elsif
6607                           not Conforming_Types
6608                             (Etype (F1), Etype (F2), Type_Conformant)
6609                         then
6610                            May_Hide_Profile := False;
6611                         end if;
6612
6613                         Next_Formal (F1);
6614                         Next_Formal (F2);
6615                      end loop;
6616
6617                      if May_Hide_Profile
6618                        and then No (F1)
6619                        and then No (F2)
6620                      then
6621                         Error_Msg_NE ("calls to& may be ambiguous?", S, S);
6622                      end if;
6623                   end;
6624                end if;
6625             end if;
6626
6627             E := Homonym (E);
6628          end loop;
6629
6630          <<Add_New_Entity>>
6631
6632          --  On exit, we know that S is a new entity
6633
6634          Enter_Overloaded_Entity (S);
6635          Maybe_Primitive_Operation;
6636          Check_Overriding_Indicator (S, Overridden_Subp);
6637
6638          --  If S is a derived operation for an untagged type then by
6639          --  definition it's not a dispatching operation (even if the parent
6640          --  operation was dispatching), so we don't call
6641          --  Check_Dispatching_Operation in that case.
6642
6643          if No (Derived_Type)
6644            or else Is_Tagged_Type (Derived_Type)
6645          then
6646             Check_Dispatching_Operation (S, Empty);
6647          end if;
6648       end if;
6649
6650       --  If this is a user-defined equality operator that is not a derived
6651       --  subprogram, create the corresponding inequality. If the operation is
6652       --  dispatching, the expansion is done elsewhere, and we do not create
6653       --  an explicit inequality operation.
6654
6655       <<Check_Inequality>>
6656          if Chars (S) = Name_Op_Eq
6657            and then Etype (S) = Standard_Boolean
6658            and then Present (Parent (S))
6659            and then not Is_Dispatching_Operation (S)
6660          then
6661             Make_Inequality_Operator (S);
6662          end if;
6663    end New_Overloaded_Entity;
6664
6665    ---------------------
6666    -- Process_Formals --
6667    ---------------------
6668
6669    procedure Process_Formals
6670      (T           : List_Id;
6671       Related_Nod : Node_Id)
6672    is
6673       Param_Spec  : Node_Id;
6674       Formal      : Entity_Id;
6675       Formal_Type : Entity_Id;
6676       Default     : Node_Id;
6677       Ptype       : Entity_Id;
6678
6679       function Is_Class_Wide_Default (D : Node_Id) return Boolean;
6680       --  Check whether the default has a class-wide type. After analysis the
6681       --  default has the type of the formal, so we must also check explicitly
6682       --  for an access attribute.
6683
6684       ---------------------------
6685       -- Is_Class_Wide_Default --
6686       ---------------------------
6687
6688       function Is_Class_Wide_Default (D : Node_Id) return Boolean is
6689       begin
6690          return Is_Class_Wide_Type (Designated_Type (Etype (D)))
6691            or else (Nkind (D) =  N_Attribute_Reference
6692                       and then Attribute_Name (D) = Name_Access
6693                       and then Is_Class_Wide_Type (Etype (Prefix (D))));
6694       end Is_Class_Wide_Default;
6695
6696    --  Start of processing for Process_Formals
6697
6698    begin
6699       --  In order to prevent premature use of the formals in the same formal
6700       --  part, the Ekind is left undefined until all default expressions are
6701       --  analyzed. The Ekind is established in a separate loop at the end.
6702
6703       Param_Spec := First (T);
6704
6705       while Present (Param_Spec) loop
6706
6707          Formal := Defining_Identifier (Param_Spec);
6708          Enter_Name (Formal);
6709
6710          --  Case of ordinary parameters
6711
6712          if Nkind (Parameter_Type (Param_Spec)) /= N_Access_Definition then
6713             Find_Type (Parameter_Type (Param_Spec));
6714             Ptype := Parameter_Type (Param_Spec);
6715
6716             if Ptype = Error then
6717                goto Continue;
6718             end if;
6719
6720             Formal_Type := Entity (Ptype);
6721
6722             if Is_Incomplete_Type (Formal_Type)
6723               or else
6724                (Is_Class_Wide_Type (Formal_Type)
6725                   and then Is_Incomplete_Type (Root_Type (Formal_Type)))
6726             then
6727                --  Ada 2005 (AI-326): Tagged incomplete types allowed
6728
6729                if Is_Tagged_Type (Formal_Type) then
6730                   null;
6731
6732                --  Special handling of Value_Type for CIL case
6733
6734                elsif Is_Value_Type (Formal_Type) then
6735                   null;
6736
6737                elsif Nkind (Parent (T)) /= N_Access_Function_Definition
6738                  and then Nkind (Parent (T)) /= N_Access_Procedure_Definition
6739                then
6740                   Error_Msg_N ("invalid use of incomplete type", Param_Spec);
6741
6742                --  An incomplete type that is not tagged is allowed in an
6743                --  access-to-subprogram type only if it is a local declaration
6744                --  with a forthcoming completion (3.10.1 (9.2/2)).
6745
6746                elsif Scope (Formal_Type) /= Scope (Current_Scope) then
6747                   Error_Msg_N
6748                     ("invalid use of limited view of type", Param_Spec);
6749                end if;
6750
6751             elsif Ekind (Formal_Type) = E_Void then
6752                Error_Msg_NE ("premature use of&",
6753                  Parameter_Type (Param_Spec), Formal_Type);
6754             end if;
6755
6756             --  Ada 2005 (AI-231): Create and decorate an internal subtype
6757             --  declaration corresponding to the null-excluding type of the
6758             --  formal in the enclosing scope. Finally, replace the parameter
6759             --  type of the formal with the internal subtype.
6760
6761             if Ada_Version >= Ada_05
6762               and then Null_Exclusion_Present (Param_Spec)
6763             then
6764                if not Is_Access_Type (Formal_Type) then
6765                   Error_Msg_N
6766                     ("`NOT NULL` allowed only for an access type", Param_Spec);
6767
6768                else
6769                   if Can_Never_Be_Null (Formal_Type)
6770                     and then Comes_From_Source (Related_Nod)
6771                   then
6772                      Error_Msg_NE
6773                        ("`NOT NULL` not allowed (& already excludes null)",
6774                         Param_Spec,
6775                         Formal_Type);
6776                   end if;
6777
6778                   Formal_Type :=
6779                     Create_Null_Excluding_Itype
6780                       (T           => Formal_Type,
6781                        Related_Nod => Related_Nod,
6782                        Scope_Id    => Scope (Current_Scope));
6783
6784                   --  If the designated type of the itype is an itype we
6785                   --  decorate it with the Has_Delayed_Freeze attribute to
6786                   --  avoid problems with the backend.
6787
6788                   --  Example:
6789                   --     type T is access procedure;
6790                   --     procedure Op (O : not null T);
6791
6792                   if Is_Itype (Directly_Designated_Type (Formal_Type)) then
6793                      Set_Has_Delayed_Freeze (Formal_Type);
6794                   end if;
6795                end if;
6796             end if;
6797
6798          --  An access formal type
6799
6800          else
6801             Formal_Type :=
6802               Access_Definition (Related_Nod, Parameter_Type (Param_Spec));
6803
6804             --  No need to continue if we already notified errors
6805
6806             if not Present (Formal_Type) then
6807                return;
6808             end if;
6809
6810             --  Ada 2005 (AI-254)
6811
6812             declare
6813                AD : constant Node_Id :=
6814                       Access_To_Subprogram_Definition
6815                         (Parameter_Type (Param_Spec));
6816             begin
6817                if Present (AD) and then Protected_Present (AD) then
6818                   Formal_Type :=
6819                     Replace_Anonymous_Access_To_Protected_Subprogram
6820                       (Param_Spec);
6821                end if;
6822             end;
6823          end if;
6824
6825          Set_Etype (Formal, Formal_Type);
6826          Default := Expression (Param_Spec);
6827
6828          if Present (Default) then
6829             if Out_Present (Param_Spec) then
6830                Error_Msg_N
6831                  ("default initialization only allowed for IN parameters",
6832                   Param_Spec);
6833             end if;
6834
6835             --  Do the special preanalysis of the expression (see section on
6836             --  "Handling of Default Expressions" in the spec of package Sem).
6837
6838             Analyze_Per_Use_Expression (Default, Formal_Type);
6839
6840             --  Check that the designated type of an access parameter's default
6841             --  is not a class-wide type unless the parameter's designated type
6842             --  is also class-wide.
6843
6844             if Ekind (Formal_Type) = E_Anonymous_Access_Type
6845               and then not From_With_Type (Formal_Type)
6846               and then Is_Class_Wide_Default (Default)
6847               and then not Is_Class_Wide_Type (Designated_Type (Formal_Type))
6848             then
6849                Error_Msg_N
6850                  ("access to class-wide expression not allowed here", Default);
6851             end if;
6852          end if;
6853
6854          --  Ada 2005 (AI-231): Static checks
6855
6856          if Ada_Version >= Ada_05
6857            and then Is_Access_Type (Etype (Formal))
6858            and then Can_Never_Be_Null (Etype (Formal))
6859          then
6860             Null_Exclusion_Static_Checks (Param_Spec);
6861          end if;
6862
6863       <<Continue>>
6864          Next (Param_Spec);
6865       end loop;
6866
6867       --  If this is the formal part of a function specification, analyze the
6868       --  subtype mark in the context where the formals are visible but not
6869       --  yet usable, and may hide outer homographs.
6870
6871       if Nkind (Related_Nod) = N_Function_Specification then
6872          Analyze_Return_Type (Related_Nod);
6873       end if;
6874
6875       --  Now set the kind (mode) of each formal
6876
6877       Param_Spec := First (T);
6878
6879       while Present (Param_Spec) loop
6880          Formal := Defining_Identifier (Param_Spec);
6881          Set_Formal_Mode (Formal);
6882
6883          if Ekind (Formal) = E_In_Parameter then
6884             Set_Default_Value (Formal, Expression (Param_Spec));
6885
6886             if Present (Expression (Param_Spec)) then
6887                Default :=  Expression (Param_Spec);
6888
6889                if Is_Scalar_Type (Etype (Default)) then
6890                   if Nkind
6891                        (Parameter_Type (Param_Spec)) /= N_Access_Definition
6892                   then
6893                      Formal_Type := Entity (Parameter_Type (Param_Spec));
6894
6895                   else
6896                      Formal_Type := Access_Definition
6897                        (Related_Nod, Parameter_Type (Param_Spec));
6898                   end if;
6899
6900                   Apply_Scalar_Range_Check (Default, Formal_Type);
6901                end if;
6902             end if;
6903          end if;
6904
6905          Next (Param_Spec);
6906       end loop;
6907
6908    end Process_Formals;
6909
6910    ----------------------------
6911    -- Reference_Body_Formals --
6912    ----------------------------
6913
6914    procedure Reference_Body_Formals (Spec : Entity_Id; Bod : Entity_Id) is
6915       Fs : Entity_Id;
6916       Fb : Entity_Id;
6917
6918    begin
6919       if Error_Posted (Spec) then
6920          return;
6921       end if;
6922
6923       --  Iterate over both lists. They may be of different lengths if the two
6924       --  specs are not conformant.
6925
6926       Fs := First_Formal (Spec);
6927       Fb := First_Formal (Bod);
6928       while Present (Fs) and then Present (Fb) loop
6929          Generate_Reference (Fs, Fb, 'b');
6930
6931          if Style_Check then
6932             Style.Check_Identifier (Fb, Fs);
6933          end if;
6934
6935          Set_Spec_Entity (Fb, Fs);
6936          Set_Referenced (Fs, False);
6937          Next_Formal (Fs);
6938          Next_Formal (Fb);
6939       end loop;
6940    end Reference_Body_Formals;
6941
6942    -------------------------
6943    -- Set_Actual_Subtypes --
6944    -------------------------
6945
6946    procedure Set_Actual_Subtypes (N : Node_Id; Subp : Entity_Id) is
6947       Loc            : constant Source_Ptr := Sloc (N);
6948       Decl           : Node_Id;
6949       Formal         : Entity_Id;
6950       T              : Entity_Id;
6951       First_Stmt     : Node_Id := Empty;
6952       AS_Needed      : Boolean;
6953
6954    begin
6955       --  If this is an emtpy initialization procedure, no need to create
6956       --  actual subtypes (small optimization).
6957
6958       if Ekind (Subp) = E_Procedure
6959         and then Is_Null_Init_Proc (Subp)
6960       then
6961          return;
6962       end if;
6963
6964       Formal := First_Formal (Subp);
6965       while Present (Formal) loop
6966          T := Etype (Formal);
6967
6968          --  We never need an actual subtype for a constrained formal
6969
6970          if Is_Constrained (T) then
6971             AS_Needed := False;
6972
6973          --  If we have unknown discriminants, then we do not need an actual
6974          --  subtype, or more accurately we cannot figure it out! Note that
6975          --  all class-wide types have unknown discriminants.
6976
6977          elsif Has_Unknown_Discriminants (T) then
6978             AS_Needed := False;
6979
6980          --  At this stage we have an unconstrained type that may need an
6981          --  actual subtype. For sure the actual subtype is needed if we have
6982          --  an unconstrained array type.
6983
6984          elsif Is_Array_Type (T) then
6985             AS_Needed := True;
6986
6987          --  The only other case needing an actual subtype is an unconstrained
6988          --  record type which is an IN parameter (we cannot generate actual
6989          --  subtypes for the OUT or IN OUT case, since an assignment can
6990          --  change the discriminant values. However we exclude the case of
6991          --  initialization procedures, since discriminants are handled very
6992          --  specially in this context, see the section entitled "Handling of
6993          --  Discriminants" in Einfo.
6994
6995          --  We also exclude the case of Discrim_SO_Functions (functions used
6996          --  in front end layout mode for size/offset values), since in such
6997          --  functions only discriminants are referenced, and not only are such
6998          --  subtypes not needed, but they cannot always be generated, because
6999          --  of order of elaboration issues.
7000
7001          elsif Is_Record_Type (T)
7002            and then Ekind (Formal) = E_In_Parameter
7003            and then Chars (Formal) /= Name_uInit
7004            and then not Is_Unchecked_Union (T)
7005            and then not Is_Discrim_SO_Function (Subp)
7006          then
7007             AS_Needed := True;
7008
7009          --  All other cases do not need an actual subtype
7010
7011          else
7012             AS_Needed := False;
7013          end if;
7014
7015          --  Generate actual subtypes for unconstrained arrays and
7016          --  unconstrained discriminated records.
7017
7018          if AS_Needed then
7019             if Nkind (N) = N_Accept_Statement then
7020
7021                --  If expansion is active, The formal is replaced by a local
7022                --  variable that renames the corresponding entry of the
7023                --  parameter block, and it is this local variable that may
7024                --  require an actual subtype.
7025
7026                if Expander_Active then
7027                   Decl := Build_Actual_Subtype (T, Renamed_Object (Formal));
7028                else
7029                   Decl := Build_Actual_Subtype (T, Formal);
7030                end if;
7031
7032                if Present (Handled_Statement_Sequence (N)) then
7033                   First_Stmt :=
7034                     First (Statements (Handled_Statement_Sequence (N)));
7035                   Prepend (Decl, Statements (Handled_Statement_Sequence (N)));
7036                   Mark_Rewrite_Insertion (Decl);
7037                else
7038                   --  If the accept statement has no body, there will be no
7039                   --  reference to the actuals, so no need to compute actual
7040                   --  subtypes.
7041
7042                   return;
7043                end if;
7044
7045             else
7046                Decl := Build_Actual_Subtype (T, Formal);
7047                Prepend (Decl, Declarations (N));
7048                Mark_Rewrite_Insertion (Decl);
7049             end if;
7050
7051             --  The declaration uses the bounds of an existing object, and
7052             --  therefore needs no constraint checks.
7053
7054             Analyze (Decl, Suppress => All_Checks);
7055
7056             --  We need to freeze manually the generated type when it is
7057             --  inserted anywhere else than in a declarative part.
7058
7059             if Present (First_Stmt) then
7060                Insert_List_Before_And_Analyze (First_Stmt,
7061                  Freeze_Entity (Defining_Identifier (Decl), Loc));
7062             end if;
7063
7064             if Nkind (N) = N_Accept_Statement
7065               and then Expander_Active
7066             then
7067                Set_Actual_Subtype (Renamed_Object (Formal),
7068                  Defining_Identifier (Decl));
7069             else
7070                Set_Actual_Subtype (Formal, Defining_Identifier (Decl));
7071             end if;
7072          end if;
7073
7074          Next_Formal (Formal);
7075       end loop;
7076    end Set_Actual_Subtypes;
7077
7078    ---------------------
7079    -- Set_Formal_Mode --
7080    ---------------------
7081
7082    procedure Set_Formal_Mode (Formal_Id : Entity_Id) is
7083       Spec : constant Node_Id := Parent (Formal_Id);
7084
7085    begin
7086       --  Note: we set Is_Known_Valid for IN parameters and IN OUT parameters
7087       --  since we ensure that corresponding actuals are always valid at the
7088       --  point of the call.
7089
7090       if Out_Present (Spec) then
7091          if Ekind (Scope (Formal_Id)) = E_Function
7092            or else Ekind (Scope (Formal_Id)) = E_Generic_Function
7093          then
7094             Error_Msg_N ("functions can only have IN parameters", Spec);
7095             Set_Ekind (Formal_Id, E_In_Parameter);
7096
7097          elsif In_Present (Spec) then
7098             Set_Ekind (Formal_Id, E_In_Out_Parameter);
7099
7100          else
7101             Set_Ekind               (Formal_Id, E_Out_Parameter);
7102             Set_Never_Set_In_Source (Formal_Id, True);
7103             Set_Is_True_Constant    (Formal_Id, False);
7104             Set_Current_Value       (Formal_Id, Empty);
7105          end if;
7106
7107       else
7108          Set_Ekind (Formal_Id, E_In_Parameter);
7109       end if;
7110
7111       --  Set Is_Known_Non_Null for access parameters since the language
7112       --  guarantees that access parameters are always non-null. We also set
7113       --  Can_Never_Be_Null, since there is no way to change the value.
7114
7115       if Nkind (Parameter_Type (Spec)) = N_Access_Definition then
7116
7117          --  Ada 2005 (AI-231): In Ada95, access parameters are always non-
7118          --  null; In Ada 2005, only if then null_exclusion is explicit.
7119
7120          if Ada_Version < Ada_05
7121            or else Can_Never_Be_Null (Etype (Formal_Id))
7122          then
7123             Set_Is_Known_Non_Null (Formal_Id);
7124             Set_Can_Never_Be_Null (Formal_Id);
7125          end if;
7126
7127       --  Ada 2005 (AI-231): Null-exclusion access subtype
7128
7129       elsif Is_Access_Type (Etype (Formal_Id))
7130         and then Can_Never_Be_Null (Etype (Formal_Id))
7131       then
7132          Set_Is_Known_Non_Null (Formal_Id);
7133       end if;
7134
7135       Set_Mechanism (Formal_Id, Default_Mechanism);
7136       Set_Formal_Validity (Formal_Id);
7137    end Set_Formal_Mode;
7138
7139    -------------------------
7140    -- Set_Formal_Validity --
7141    -------------------------
7142
7143    procedure Set_Formal_Validity (Formal_Id : Entity_Id) is
7144    begin
7145       --  If no validity checking, then we cannot assume anything about the
7146       --  validity of parameters, since we do not know there is any checking
7147       --  of the validity on the call side.
7148
7149       if not Validity_Checks_On then
7150          return;
7151
7152       --  If validity checking for parameters is enabled, this means we are
7153       --  not supposed to make any assumptions about argument values.
7154
7155       elsif Validity_Check_Parameters then
7156          return;
7157
7158       --  If we are checking in parameters, we will assume that the caller is
7159       --  also checking parameters, so we can assume the parameter is valid.
7160
7161       elsif Ekind (Formal_Id) = E_In_Parameter
7162         and then Validity_Check_In_Params
7163       then
7164          Set_Is_Known_Valid (Formal_Id, True);
7165
7166       --  Similar treatment for IN OUT parameters
7167
7168       elsif Ekind (Formal_Id) = E_In_Out_Parameter
7169         and then Validity_Check_In_Out_Params
7170       then
7171          Set_Is_Known_Valid (Formal_Id, True);
7172       end if;
7173    end Set_Formal_Validity;
7174
7175    ------------------------
7176    -- Subtype_Conformant --
7177    ------------------------
7178
7179    function Subtype_Conformant (New_Id, Old_Id : Entity_Id) return Boolean is
7180       Result : Boolean;
7181    begin
7182       Check_Conformance (New_Id, Old_Id, Subtype_Conformant, False, Result);
7183       return Result;
7184    end Subtype_Conformant;
7185
7186    ---------------------
7187    -- Type_Conformant --
7188    ---------------------
7189
7190    function Type_Conformant
7191      (New_Id                   : Entity_Id;
7192       Old_Id                   : Entity_Id;
7193       Skip_Controlling_Formals : Boolean := False) return Boolean
7194    is
7195       Result : Boolean;
7196    begin
7197       May_Hide_Profile := False;
7198
7199       Check_Conformance
7200         (New_Id, Old_Id, Type_Conformant, False, Result,
7201          Skip_Controlling_Formals => Skip_Controlling_Formals);
7202       return Result;
7203    end Type_Conformant;
7204
7205    -------------------------------
7206    -- Valid_Operator_Definition --
7207    -------------------------------
7208
7209    procedure Valid_Operator_Definition (Designator : Entity_Id) is
7210       N    : Integer := 0;
7211       F    : Entity_Id;
7212       Id   : constant Name_Id := Chars (Designator);
7213       N_OK : Boolean;
7214
7215    begin
7216       F := First_Formal (Designator);
7217       while Present (F) loop
7218          N := N + 1;
7219
7220          if Present (Default_Value (F)) then
7221             Error_Msg_N
7222               ("default values not allowed for operator parameters",
7223                Parent (F));
7224          end if;
7225
7226          Next_Formal (F);
7227       end loop;
7228
7229       --  Verify that user-defined operators have proper number of arguments
7230       --  First case of operators which can only be unary
7231
7232       if Id = Name_Op_Not
7233         or else Id = Name_Op_Abs
7234       then
7235          N_OK := (N = 1);
7236
7237       --  Case of operators which can be unary or binary
7238
7239       elsif Id = Name_Op_Add
7240         or Id = Name_Op_Subtract
7241       then
7242          N_OK := (N in 1 .. 2);
7243
7244       --  All other operators can only be binary
7245
7246       else
7247          N_OK := (N = 2);
7248       end if;
7249
7250       if not N_OK then
7251          Error_Msg_N
7252            ("incorrect number of arguments for operator", Designator);
7253       end if;
7254
7255       if Id = Name_Op_Ne
7256         and then Base_Type (Etype (Designator)) = Standard_Boolean
7257         and then not Is_Intrinsic_Subprogram (Designator)
7258       then
7259          Error_Msg_N
7260             ("explicit definition of inequality not allowed", Designator);
7261       end if;
7262    end Valid_Operator_Definition;
7263
7264 end Sem_Ch6;