PR ipa/64481
[official-gcc.git] / gcc / ada / sem_ch6.adb
blob1335dcf5a867e30e1ed899a26a5b3125da9fd1b9
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-2014, Free Software Foundation, Inc. --
10 -- --
11 -- GNAT is free software; you can redistribute it and/or modify it under --
12 -- terms of the GNU General Public License as published by the Free Soft- --
13 -- ware Foundation; either version 3, or (at your option) any later ver- --
14 -- sion. GNAT is distributed in the hope that it will be useful, but WITH- --
15 -- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY --
16 -- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License --
17 -- for more details. You should have received a copy of the GNU General --
18 -- Public License distributed with GNAT; see file COPYING3. If not, go to --
19 -- http://www.gnu.org/licenses for a complete copy of the license. --
20 -- --
21 -- GNAT was originally developed by the GNAT team at New York University. --
22 -- Extensive contributions were provided by Ada Core Technologies Inc. --
23 -- --
24 ------------------------------------------------------------------------------
26 with Aspects; use Aspects;
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_Ch9; use Exp_Ch9;
37 with Exp_Dbug; use Exp_Dbug;
38 with Exp_Disp; use Exp_Disp;
39 with Exp_Tss; use Exp_Tss;
40 with Exp_Util; use Exp_Util;
41 with Fname; use Fname;
42 with Freeze; use Freeze;
43 with Ghost; use Ghost;
44 with Inline; use Inline;
45 with Itypes; use Itypes;
46 with Lib.Xref; use Lib.Xref;
47 with Layout; use Layout;
48 with Namet; use Namet;
49 with Lib; use Lib;
50 with Nlists; use Nlists;
51 with Nmake; use Nmake;
52 with Opt; use Opt;
53 with Output; use Output;
54 with Restrict; use Restrict;
55 with Rident; use Rident;
56 with Rtsfind; use Rtsfind;
57 with Sem; use Sem;
58 with Sem_Aux; use Sem_Aux;
59 with Sem_Cat; use Sem_Cat;
60 with Sem_Ch3; use Sem_Ch3;
61 with Sem_Ch4; use Sem_Ch4;
62 with Sem_Ch5; use Sem_Ch5;
63 with Sem_Ch8; use Sem_Ch8;
64 with Sem_Ch10; use Sem_Ch10;
65 with Sem_Ch12; use Sem_Ch12;
66 with Sem_Ch13; use Sem_Ch13;
67 with Sem_Dim; use Sem_Dim;
68 with Sem_Disp; use Sem_Disp;
69 with Sem_Dist; use Sem_Dist;
70 with Sem_Elim; use Sem_Elim;
71 with Sem_Eval; use Sem_Eval;
72 with Sem_Mech; use Sem_Mech;
73 with Sem_Prag; use Sem_Prag;
74 with Sem_Res; use Sem_Res;
75 with Sem_Util; use Sem_Util;
76 with Sem_Type; use Sem_Type;
77 with Sem_Warn; use Sem_Warn;
78 with Sinput; use Sinput;
79 with Stand; use Stand;
80 with Sinfo; use Sinfo;
81 with Sinfo.CN; use Sinfo.CN;
82 with Snames; use Snames;
83 with Stringt; use Stringt;
84 with Style;
85 with Stylesw; use Stylesw;
86 with Targparm; use Targparm;
87 with Tbuild; use Tbuild;
88 with Uintp; use Uintp;
89 with Urealp; use Urealp;
90 with Validsw; use Validsw;
92 package body Sem_Ch6 is
94 May_Hide_Profile : Boolean := False;
95 -- This flag is used to indicate that two formals in two subprograms being
96 -- checked for conformance differ only in that one is an access parameter
97 -- while the other is of a general access type with the same designated
98 -- type. In this case, if the rest of the signatures match, a call to
99 -- either subprogram may be ambiguous, which is worth a warning. The flag
100 -- is set in Compatible_Types, and the warning emitted in
101 -- New_Overloaded_Entity.
103 -----------------------
104 -- Local Subprograms --
105 -----------------------
107 procedure Analyze_Null_Procedure
108 (N : Node_Id;
109 Is_Completion : out Boolean);
110 -- A null procedure can be a declaration or (Ada 2012) a completion
112 procedure Analyze_Return_Statement (N : Node_Id);
113 -- Common processing for simple and extended return statements
115 procedure Analyze_Function_Return (N : Node_Id);
116 -- Subsidiary to Analyze_Return_Statement. Called when the return statement
117 -- applies to a [generic] function.
119 procedure Analyze_Return_Type (N : Node_Id);
120 -- Subsidiary to Process_Formals: analyze subtype mark in function
121 -- specification in a context where the formals are visible and hide
122 -- outer homographs.
124 procedure Analyze_Subprogram_Body_Helper (N : Node_Id);
125 -- Does all the real work of Analyze_Subprogram_Body. This is split out so
126 -- that we can use RETURN but not skip the debug output at the end.
128 procedure Analyze_Generic_Subprogram_Body (N : Node_Id; Gen_Id : Entity_Id);
129 -- Analyze a generic subprogram body. N is the body to be analyzed, and
130 -- Gen_Id is the defining entity Id for the corresponding spec.
132 function Can_Override_Operator (Subp : Entity_Id) return Boolean;
133 -- Returns true if Subp can override a predefined operator.
135 procedure Check_Conformance
136 (New_Id : Entity_Id;
137 Old_Id : Entity_Id;
138 Ctype : Conformance_Type;
139 Errmsg : Boolean;
140 Conforms : out Boolean;
141 Err_Loc : Node_Id := Empty;
142 Get_Inst : Boolean := False;
143 Skip_Controlling_Formals : Boolean := False);
144 -- Given two entities, this procedure checks that the profiles associated
145 -- with these entities meet the conformance criterion given by the third
146 -- parameter. If they conform, Conforms is set True and control returns
147 -- to the caller. If they do not conform, Conforms is set to False, and
148 -- in addition, if Errmsg is True on the call, proper messages are output
149 -- to complain about the conformance failure. If Err_Loc is non_Empty
150 -- the error messages are placed on Err_Loc, if Err_Loc is empty, then
151 -- error messages are placed on the appropriate part of the construct
152 -- denoted by New_Id. If Get_Inst is true, then this is a mode conformance
153 -- against a formal access-to-subprogram type so Get_Instance_Of must
154 -- be called.
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.
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.
175 procedure Check_Untagged_Equality (Eq_Op : Entity_Id);
176 -- In Ada 2012, a primitive equality operator on an untagged record type
177 -- must appear before the type is frozen, and have the same visibility as
178 -- that of the type. This procedure checks that this rule is met, and
179 -- otherwise emits an error on the subprogram declaration and a warning
180 -- on the earlier freeze point if it is easy to locate. In Ada 2012 mode,
181 -- this routine outputs errors (or warnings if -gnatd.E is set). In earlier
182 -- versions of Ada, warnings are output if Warn_On_Ada_2012_Incompatibility
183 -- is set, otherwise the call has no effect.
185 procedure Enter_Overloaded_Entity (S : Entity_Id);
186 -- This procedure makes S, a new overloaded entity, into the first visible
187 -- entity with that name.
189 function Is_Non_Overriding_Operation
190 (Prev_E : Entity_Id;
191 New_E : Entity_Id) return Boolean;
192 -- Enforce the rule given in 12.3(18): a private operation in an instance
193 -- overrides an inherited operation only if the corresponding operation
194 -- was overriding in the generic. This needs to be checked for primitive
195 -- operations of types derived (in the generic unit) from formal private
196 -- or formal derived types.
198 procedure Make_Inequality_Operator (S : Entity_Id);
199 -- Create the declaration for an inequality operator that is implicitly
200 -- created by a user-defined equality operator that yields a boolean.
202 procedure Set_Formal_Validity (Formal_Id : Entity_Id);
203 -- Formal_Id is an formal parameter entity. This procedure deals with
204 -- setting the proper validity status for this entity, which depends on
205 -- the kind of parameter and the validity checking mode.
207 ---------------------------------------------
208 -- Analyze_Abstract_Subprogram_Declaration --
209 ---------------------------------------------
211 procedure Analyze_Abstract_Subprogram_Declaration (N : Node_Id) is
212 Designator : constant Entity_Id :=
213 Analyze_Subprogram_Specification (Specification (N));
214 Scop : constant Entity_Id := Current_Scope;
216 begin
217 -- The abstract subprogram declaration may be subject to pragma Ghost
218 -- with policy Ignore. Set the mode now to ensure that any nodes
219 -- generated during analysis and expansion are properly flagged as
220 -- ignored Ghost.
222 Set_Ghost_Mode (N);
223 Check_SPARK_05_Restriction ("abstract subprogram is not allowed", N);
225 Generate_Definition (Designator);
226 Set_Contract (Designator, Make_Contract (Sloc (Designator)));
227 Set_Is_Abstract_Subprogram (Designator);
228 New_Overloaded_Entity (Designator);
229 Check_Delayed_Subprogram (Designator);
231 Set_Categorization_From_Scope (Designator, Scop);
233 -- An abstract subprogram declared within a Ghost region is rendered
234 -- Ghost (SPARK RM 6.9(2)).
236 if Comes_From_Source (Designator) and then Ghost_Mode > None then
237 Set_Is_Ghost_Entity (Designator);
238 end if;
240 if Ekind (Scope (Designator)) = E_Protected_Type then
241 Error_Msg_N
242 ("abstract subprogram not allowed in protected type", N);
244 -- Issue a warning if the abstract subprogram is neither a dispatching
245 -- operation nor an operation that overrides an inherited subprogram or
246 -- predefined operator, since this most likely indicates a mistake.
248 elsif Warn_On_Redundant_Constructs
249 and then not Is_Dispatching_Operation (Designator)
250 and then not Present (Overridden_Operation (Designator))
251 and then (not Is_Operator_Symbol_Name (Chars (Designator))
252 or else Scop /= Scope (Etype (First_Formal (Designator))))
253 then
254 Error_Msg_N
255 ("abstract subprogram is not dispatching or overriding?r?", N);
256 end if;
258 Generate_Reference_To_Formals (Designator);
259 Check_Eliminated (Designator);
261 if Has_Aspects (N) then
262 Analyze_Aspect_Specifications (N, Designator);
263 end if;
264 end Analyze_Abstract_Subprogram_Declaration;
266 ---------------------------------
267 -- Analyze_Expression_Function --
268 ---------------------------------
270 procedure Analyze_Expression_Function (N : Node_Id) is
271 Loc : constant Source_Ptr := Sloc (N);
272 LocX : constant Source_Ptr := Sloc (Expression (N));
273 Expr : constant Node_Id := Expression (N);
274 Spec : constant Node_Id := Specification (N);
276 Def_Id : Entity_Id;
278 Prev : Entity_Id;
279 -- If the expression is a completion, Prev is the entity whose
280 -- declaration is completed. Def_Id is needed to analyze the spec.
282 New_Body : Node_Id;
283 New_Spec : Node_Id;
284 Ret : Node_Id;
286 begin
287 -- This is one of the occasions on which we transform the tree during
288 -- semantic analysis. If this is a completion, transform the expression
289 -- function into an equivalent subprogram body, and analyze it.
291 -- Expression functions are inlined unconditionally. The back-end will
292 -- determine whether this is possible.
294 Inline_Processing_Required := True;
296 -- Create a specification for the generated body. Types and defauts in
297 -- the profile are copies of the spec, but new entities must be created
298 -- for the unit name and the formals.
300 New_Spec := New_Copy_Tree (Spec);
301 Set_Defining_Unit_Name (New_Spec,
302 Make_Defining_Identifier (Sloc (Defining_Unit_Name (Spec)),
303 Chars (Defining_Unit_Name (Spec))));
305 if Present (Parameter_Specifications (New_Spec)) then
306 declare
307 Formal_Spec : Node_Id;
308 Def : Entity_Id;
310 begin
311 Formal_Spec := First (Parameter_Specifications (New_Spec));
313 -- Create a new formal parameter at the same source position
315 while Present (Formal_Spec) loop
316 Def := Defining_Identifier (Formal_Spec);
317 Set_Defining_Identifier (Formal_Spec,
318 Make_Defining_Identifier (Sloc (Def),
319 Chars => Chars (Def)));
320 Next (Formal_Spec);
321 end loop;
322 end;
323 end if;
325 Prev := Current_Entity_In_Scope (Defining_Entity (Spec));
327 -- If there are previous overloadable entities with the same name,
328 -- check whether any of them is completed by the expression function.
329 -- In a generic context a formal subprogram has no completion.
331 if Present (Prev)
332 and then Is_Overloadable (Prev)
333 and then not Is_Formal_Subprogram (Prev)
334 then
335 Def_Id := Analyze_Subprogram_Specification (Spec);
336 Prev := Find_Corresponding_Spec (N);
338 -- The previous entity may be an expression function as well, in
339 -- which case the redeclaration is illegal.
341 if Present (Prev)
342 and then Nkind (Original_Node (Unit_Declaration_Node (Prev))) =
343 N_Expression_Function
344 then
345 Error_Msg_Sloc := Sloc (Prev);
346 Error_Msg_N ("& conflicts with declaration#", Def_Id);
347 return;
348 end if;
349 end if;
351 Ret := Make_Simple_Return_Statement (LocX, Expression (N));
353 New_Body :=
354 Make_Subprogram_Body (Loc,
355 Specification => New_Spec,
356 Declarations => Empty_List,
357 Handled_Statement_Sequence =>
358 Make_Handled_Sequence_Of_Statements (LocX,
359 Statements => New_List (Ret)));
361 -- If the expression completes a generic subprogram, we must create a
362 -- separate node for the body, because at instantiation the original
363 -- node of the generic copy must be a generic subprogram body, and
364 -- cannot be a expression function. Otherwise we just rewrite the
365 -- expression with the non-generic body.
367 if Present (Prev) and then Ekind (Prev) = E_Generic_Function then
368 Insert_After (N, New_Body);
370 -- Propagate any aspects or pragmas that apply to the expression
371 -- function to the proper body when the expression function acts
372 -- as a completion.
374 if Has_Aspects (N) then
375 Move_Aspects (N, To => New_Body);
376 end if;
378 Relocate_Pragmas_To_Body (New_Body);
380 Rewrite (N, Make_Null_Statement (Loc));
381 Set_Has_Completion (Prev, False);
382 Analyze (N);
383 Analyze (New_Body);
384 Set_Is_Inlined (Prev);
386 -- If the expression function is a completion, the previous declaration
387 -- must come from source. We know already that appears in the current
388 -- scope. The entity itself may be internally created if within a body
389 -- to be inlined.
391 elsif Present (Prev)
392 and then Comes_From_Source (Parent (Prev))
393 and then not Is_Formal_Subprogram (Prev)
394 then
395 Set_Has_Completion (Prev, False);
397 -- An expression function that is a completion freezes the
398 -- expression. This means freezing the return type, and if it is
399 -- an access type, freezing its designated type as well.
401 -- Note that we cannot defer this freezing to the analysis of the
402 -- expression itself, because a freeze node might appear in a nested
403 -- scope, leading to an elaboration order issue in gigi.
405 Freeze_Before (N, Etype (Prev));
407 if Is_Access_Type (Etype (Prev)) then
408 Freeze_Before (N, Designated_Type (Etype (Prev)));
409 end if;
411 -- For navigation purposes, indicate that the function is a body
413 Generate_Reference (Prev, Defining_Entity (N), 'b', Force => True);
414 Rewrite (N, New_Body);
416 -- Correct the parent pointer of the aspect specification list to
417 -- reference the rewritten node.
419 if Has_Aspects (N) then
420 Set_Parent (Aspect_Specifications (N), N);
421 end if;
423 -- Propagate any pragmas that apply to the expression function to the
424 -- proper body when the expression function acts as a completion.
425 -- Aspects are automatically transfered because of node rewriting.
427 Relocate_Pragmas_To_Body (N);
428 Analyze (N);
430 -- Prev is the previous entity with the same name, but it is can
431 -- be an unrelated spec that is not completed by the expression
432 -- function. In that case the relevant entity is the one in the body.
433 -- Not clear that the backend can inline it in this case ???
435 if Has_Completion (Prev) then
436 Set_Is_Inlined (Prev);
438 -- The formals of the expression function are body formals,
439 -- and do not appear in the ali file, which will only contain
440 -- references to the formals of the original subprogram spec.
442 declare
443 F1 : Entity_Id;
444 F2 : Entity_Id;
446 begin
447 F1 := First_Formal (Def_Id);
448 F2 := First_Formal (Prev);
450 while Present (F1) loop
451 Set_Spec_Entity (F1, F2);
452 Next_Formal (F1);
453 Next_Formal (F2);
454 end loop;
455 end;
457 else
458 Set_Is_Inlined (Defining_Entity (New_Body));
459 end if;
461 -- If this is not a completion, create both a declaration and a body, so
462 -- that the expression can be inlined whenever possible.
464 else
465 -- An expression function that is not a completion is not a
466 -- subprogram declaration, and thus cannot appear in a protected
467 -- definition.
469 if Nkind (Parent (N)) = N_Protected_Definition then
470 Error_Msg_N
471 ("an expression function is not a legal protected operation", N);
472 end if;
474 Rewrite (N, Make_Subprogram_Declaration (Loc, Specification => Spec));
476 -- Correct the parent pointer of the aspect specification list to
477 -- reference the rewritten node.
479 if Has_Aspects (N) then
480 Set_Parent (Aspect_Specifications (N), N);
481 end if;
483 Analyze (N);
485 -- Within a generic pre-analyze the original expression for name
486 -- capture. The body is also generated but plays no role in
487 -- this because it is not part of the original source.
489 if Inside_A_Generic then
490 declare
491 Id : constant Entity_Id := Defining_Entity (N);
493 begin
494 Set_Has_Completion (Id);
495 Push_Scope (Id);
496 Install_Formals (Id);
497 Preanalyze_Spec_Expression (Expr, Etype (Id));
498 End_Scope;
499 end;
500 end if;
502 Set_Is_Inlined (Defining_Entity (N));
504 -- Establish the linkages between the spec and the body. These are
505 -- used when the expression function acts as the prefix of attribute
506 -- 'Access in order to freeze the original expression which has been
507 -- moved to the generated body.
509 Set_Corresponding_Body (N, Defining_Entity (New_Body));
510 Set_Corresponding_Spec (New_Body, Defining_Entity (N));
512 -- To prevent premature freeze action, insert the new body at the end
513 -- of the current declarations, or at the end of the package spec.
514 -- However, resolve usage names now, to prevent spurious visibility
515 -- on later entities. Note that the function can now be called in
516 -- the current declarative part, which will appear to be prior to
517 -- the presence of the body in the code. There are nevertheless no
518 -- order of elaboration issues because all name resolution has taken
519 -- place at the point of declaration.
521 declare
522 Decls : List_Id := List_Containing (N);
523 Par : constant Node_Id := Parent (Decls);
524 Id : constant Entity_Id := Defining_Entity (N);
526 begin
527 -- If this is a wrapper created for in an instance for a formal
528 -- subprogram, insert body after declaration, to be analyzed when
529 -- the enclosing instance is analyzed.
531 if GNATprove_Mode
532 and then Is_Generic_Actual_Subprogram (Defining_Entity (N))
533 then
534 Insert_After (N, New_Body);
536 else
537 if Nkind (Par) = N_Package_Specification
538 and then Decls = Visible_Declarations (Par)
539 and then Present (Private_Declarations (Par))
540 and then not Is_Empty_List (Private_Declarations (Par))
541 then
542 Decls := Private_Declarations (Par);
543 end if;
545 Insert_After (Last (Decls), New_Body);
546 Push_Scope (Id);
547 Install_Formals (Id);
549 -- Preanalyze the expression for name capture, except in an
550 -- instance, where this has been done during generic analysis,
551 -- and will be redone when analyzing the body.
553 declare
554 Expr : constant Node_Id := Expression (Ret);
556 begin
557 Set_Parent (Expr, Ret);
559 if not In_Instance then
560 Preanalyze_Spec_Expression (Expr, Etype (Id));
561 end if;
562 end;
564 End_Scope;
565 end if;
566 end;
567 end if;
569 -- If the return expression is a static constant, we suppress warning
570 -- messages on unused formals, which in most cases will be noise.
572 Set_Is_Trivial_Subprogram (Defining_Entity (New_Body),
573 Is_OK_Static_Expression (Expr));
574 end Analyze_Expression_Function;
576 ----------------------------------------
577 -- Analyze_Extended_Return_Statement --
578 ----------------------------------------
580 procedure Analyze_Extended_Return_Statement (N : Node_Id) is
581 begin
582 Check_Compiler_Unit ("extended return statement", N);
583 Analyze_Return_Statement (N);
584 end Analyze_Extended_Return_Statement;
586 ----------------------------
587 -- Analyze_Function_Call --
588 ----------------------------
590 procedure Analyze_Function_Call (N : Node_Id) is
591 Actuals : constant List_Id := Parameter_Associations (N);
592 Func_Nam : constant Node_Id := Name (N);
593 Actual : Node_Id;
595 begin
596 Analyze (Func_Nam);
598 -- A call of the form A.B (X) may be an Ada 2005 call, which is
599 -- rewritten as B (A, X). If the rewriting is successful, the call
600 -- has been analyzed and we just return.
602 if Nkind (Func_Nam) = N_Selected_Component
603 and then Name (N) /= Func_Nam
604 and then Is_Rewrite_Substitution (N)
605 and then Present (Etype (N))
606 then
607 return;
608 end if;
610 -- If error analyzing name, then set Any_Type as result type and return
612 if Etype (Func_Nam) = Any_Type then
613 Set_Etype (N, Any_Type);
614 return;
615 end if;
617 -- Otherwise analyze the parameters
619 if Present (Actuals) then
620 Actual := First (Actuals);
621 while Present (Actual) loop
622 Analyze (Actual);
623 Check_Parameterless_Call (Actual);
624 Next (Actual);
625 end loop;
626 end if;
628 Analyze_Call (N);
629 end Analyze_Function_Call;
631 -----------------------------
632 -- Analyze_Function_Return --
633 -----------------------------
635 procedure Analyze_Function_Return (N : Node_Id) is
636 Loc : constant Source_Ptr := Sloc (N);
637 Stm_Entity : constant Entity_Id := Return_Statement_Entity (N);
638 Scope_Id : constant Entity_Id := Return_Applies_To (Stm_Entity);
640 R_Type : constant Entity_Id := Etype (Scope_Id);
641 -- Function result subtype
643 procedure Check_Limited_Return (Expr : Node_Id);
644 -- Check the appropriate (Ada 95 or Ada 2005) rules for returning
645 -- limited types. Used only for simple return statements.
646 -- Expr is the expression returned.
648 procedure Check_Return_Subtype_Indication (Obj_Decl : Node_Id);
649 -- Check that the return_subtype_indication properly matches the result
650 -- subtype of the function, as required by RM-6.5(5.1/2-5.3/2).
652 --------------------------
653 -- Check_Limited_Return --
654 --------------------------
656 procedure Check_Limited_Return (Expr : Node_Id) is
657 begin
658 -- Ada 2005 (AI-318-02): Return-by-reference types have been
659 -- removed and replaced by anonymous access results. This is an
660 -- incompatibility with Ada 95. Not clear whether this should be
661 -- enforced yet or perhaps controllable with special switch. ???
663 -- A limited interface that is not immutably limited is OK.
665 if Is_Limited_Interface (R_Type)
666 and then
667 not (Is_Task_Interface (R_Type)
668 or else Is_Protected_Interface (R_Type)
669 or else Is_Synchronized_Interface (R_Type))
670 then
671 null;
673 elsif Is_Limited_Type (R_Type)
674 and then not Is_Interface (R_Type)
675 and then Comes_From_Source (N)
676 and then not In_Instance_Body
677 and then not OK_For_Limited_Init_In_05 (R_Type, Expr)
678 then
679 -- Error in Ada 2005
681 if Ada_Version >= Ada_2005
682 and then not Debug_Flag_Dot_L
683 and then not GNAT_Mode
684 then
685 Error_Msg_N
686 ("(Ada 2005) cannot copy object of a limited type "
687 & "(RM-2005 6.5(5.5/2))", Expr);
689 if Is_Limited_View (R_Type) then
690 Error_Msg_N
691 ("\return by reference not permitted in Ada 2005", Expr);
692 end if;
694 -- Warn in Ada 95 mode, to give folks a heads up about this
695 -- incompatibility.
697 -- In GNAT mode, this is just a warning, to allow it to be
698 -- evilly turned off. Otherwise it is a real error.
700 -- In a generic context, simplify the warning because it makes
701 -- no sense to discuss pass-by-reference or copy.
703 elsif Warn_On_Ada_2005_Compatibility or GNAT_Mode then
704 if Inside_A_Generic then
705 Error_Msg_N
706 ("return of limited object not permitted in Ada 2005 "
707 & "(RM-2005 6.5(5.5/2))?y?", Expr);
709 elsif Is_Limited_View (R_Type) then
710 Error_Msg_N
711 ("return by reference not permitted in Ada 2005 "
712 & "(RM-2005 6.5(5.5/2))?y?", Expr);
713 else
714 Error_Msg_N
715 ("cannot copy object of a limited type in Ada 2005 "
716 & "(RM-2005 6.5(5.5/2))?y?", Expr);
717 end if;
719 -- Ada 95 mode, compatibility warnings disabled
721 else
722 return; -- skip continuation messages below
723 end if;
725 if not Inside_A_Generic then
726 Error_Msg_N
727 ("\consider switching to return of access type", Expr);
728 Explain_Limited_Type (R_Type, Expr);
729 end if;
730 end if;
731 end Check_Limited_Return;
733 -------------------------------------
734 -- Check_Return_Subtype_Indication --
735 -------------------------------------
737 procedure Check_Return_Subtype_Indication (Obj_Decl : Node_Id) is
738 Return_Obj : constant Node_Id := Defining_Identifier (Obj_Decl);
740 R_Stm_Type : constant Entity_Id := Etype (Return_Obj);
741 -- Subtype given in the extended return statement (must match R_Type)
743 Subtype_Ind : constant Node_Id :=
744 Object_Definition (Original_Node (Obj_Decl));
746 R_Type_Is_Anon_Access : constant Boolean :=
747 Ekind_In (R_Type,
748 E_Anonymous_Access_Subprogram_Type,
749 E_Anonymous_Access_Protected_Subprogram_Type,
750 E_Anonymous_Access_Type);
751 -- True if return type of the function is an anonymous access type
752 -- Can't we make Is_Anonymous_Access_Type in einfo ???
754 R_Stm_Type_Is_Anon_Access : constant Boolean :=
755 Ekind_In (R_Stm_Type,
756 E_Anonymous_Access_Subprogram_Type,
757 E_Anonymous_Access_Protected_Subprogram_Type,
758 E_Anonymous_Access_Type);
759 -- True if type of the return object is an anonymous access type
761 procedure Error_No_Match (N : Node_Id);
762 -- Output error messages for case where types do not statically
763 -- match. N is the location for the messages.
765 --------------------
766 -- Error_No_Match --
767 --------------------
769 procedure Error_No_Match (N : Node_Id) is
770 begin
771 Error_Msg_N
772 ("subtype must statically match function result subtype", N);
774 if not Predicates_Match (R_Stm_Type, R_Type) then
775 Error_Msg_Node_2 := R_Type;
776 Error_Msg_NE
777 ("\predicate of& does not match predicate of&",
778 N, R_Stm_Type);
779 end if;
780 end Error_No_Match;
782 -- Start of processing for Check_Return_Subtype_Indication
784 begin
785 -- First, avoid cascaded errors
787 if Error_Posted (Obj_Decl) or else Error_Posted (Subtype_Ind) then
788 return;
789 end if;
791 -- "return access T" case; check that the return statement also has
792 -- "access T", and that the subtypes statically match:
793 -- if this is an access to subprogram the signatures must match.
795 if R_Type_Is_Anon_Access then
796 if R_Stm_Type_Is_Anon_Access then
798 Ekind (Designated_Type (R_Stm_Type)) /= E_Subprogram_Type
799 then
800 if Base_Type (Designated_Type (R_Stm_Type)) /=
801 Base_Type (Designated_Type (R_Type))
802 or else not Subtypes_Statically_Match (R_Stm_Type, R_Type)
803 then
804 Error_No_Match (Subtype_Mark (Subtype_Ind));
805 end if;
807 else
808 -- For two anonymous access to subprogram types, the
809 -- types themselves must be type conformant.
811 if not Conforming_Types
812 (R_Stm_Type, R_Type, Fully_Conformant)
813 then
814 Error_No_Match (Subtype_Ind);
815 end if;
816 end if;
818 else
819 Error_Msg_N ("must use anonymous access type", Subtype_Ind);
820 end if;
822 -- If the return object is of an anonymous access type, then report
823 -- an error if the function's result type is not also anonymous.
825 elsif R_Stm_Type_Is_Anon_Access
826 and then not R_Type_Is_Anon_Access
827 then
828 Error_Msg_N ("anonymous access not allowed for function with "
829 & "named access result", Subtype_Ind);
831 -- Subtype indication case: check that the return object's type is
832 -- covered by the result type, and that the subtypes statically match
833 -- when the result subtype is constrained. Also handle record types
834 -- with unknown discriminants for which we have built the underlying
835 -- record view. Coverage is needed to allow specific-type return
836 -- objects when the result type is class-wide (see AI05-32).
838 elsif Covers (Base_Type (R_Type), Base_Type (R_Stm_Type))
839 or else (Is_Underlying_Record_View (Base_Type (R_Stm_Type))
840 and then
841 Covers
842 (Base_Type (R_Type),
843 Underlying_Record_View (Base_Type (R_Stm_Type))))
844 then
845 -- A null exclusion may be present on the return type, on the
846 -- function specification, on the object declaration or on the
847 -- subtype itself.
849 if Is_Access_Type (R_Type)
850 and then
851 (Can_Never_Be_Null (R_Type)
852 or else Null_Exclusion_Present (Parent (Scope_Id))) /=
853 Can_Never_Be_Null (R_Stm_Type)
854 then
855 Error_No_Match (Subtype_Ind);
856 end if;
858 -- AI05-103: for elementary types, subtypes must statically match
860 if Is_Constrained (R_Type)
861 or else Is_Access_Type (R_Type)
862 then
863 if not Subtypes_Statically_Match (R_Stm_Type, R_Type) then
864 Error_No_Match (Subtype_Ind);
865 end if;
866 end if;
868 -- All remaining cases are illegal
870 -- Note: previous versions of this subprogram allowed the return
871 -- value to be the ancestor of the return type if the return type
872 -- was a null extension. This was plainly incorrect.
874 else
875 Error_Msg_N
876 ("wrong type for return_subtype_indication", Subtype_Ind);
877 end if;
878 end Check_Return_Subtype_Indication;
880 ---------------------
881 -- Local Variables --
882 ---------------------
884 Expr : Node_Id;
886 -- Start of processing for Analyze_Function_Return
888 begin
889 Set_Return_Present (Scope_Id);
891 if Nkind (N) = N_Simple_Return_Statement then
892 Expr := Expression (N);
894 -- Guard against a malformed expression. The parser may have tried to
895 -- recover but the node is not analyzable.
897 if Nkind (Expr) = N_Error then
898 Set_Etype (Expr, Any_Type);
899 Expander_Mode_Save_And_Set (False);
900 return;
902 else
903 -- The resolution of a controlled [extension] aggregate associated
904 -- with a return statement creates a temporary which needs to be
905 -- finalized on function exit. Wrap the return statement inside a
906 -- block so that the finalization machinery can detect this case.
907 -- This early expansion is done only when the return statement is
908 -- not part of a handled sequence of statements.
910 if Nkind_In (Expr, N_Aggregate,
911 N_Extension_Aggregate)
912 and then Needs_Finalization (R_Type)
913 and then Nkind (Parent (N)) /= N_Handled_Sequence_Of_Statements
914 then
915 Rewrite (N,
916 Make_Block_Statement (Loc,
917 Handled_Statement_Sequence =>
918 Make_Handled_Sequence_Of_Statements (Loc,
919 Statements => New_List (Relocate_Node (N)))));
921 Analyze (N);
922 return;
923 end if;
925 Analyze (Expr);
927 -- Ada 2005 (AI-251): If the type of the returned object is
928 -- an access to an interface type then we add an implicit type
929 -- conversion to force the displacement of the "this" pointer to
930 -- reference the secondary dispatch table. We cannot delay the
931 -- generation of this implicit conversion until the expansion
932 -- because in this case the type resolution changes the decoration
933 -- of the expression node to match R_Type; by contrast, if the
934 -- returned object is a class-wide interface type then it is too
935 -- early to generate here the implicit conversion since the return
936 -- statement may be rewritten by the expander into an extended
937 -- return statement whose expansion takes care of adding the
938 -- implicit type conversion to displace the pointer to the object.
940 if Expander_Active
941 and then Serious_Errors_Detected = 0
942 and then Is_Access_Type (R_Type)
943 and then Nkind (Expr) /= N_Null
944 and then Is_Interface (Designated_Type (R_Type))
945 and then Is_Progenitor (Designated_Type (R_Type),
946 Designated_Type (Etype (Expr)))
947 then
948 Rewrite (Expr, Convert_To (R_Type, Relocate_Node (Expr)));
949 Analyze (Expr);
950 end if;
952 Resolve (Expr, R_Type);
953 Check_Limited_Return (Expr);
954 end if;
956 -- RETURN only allowed in SPARK as the last statement in function
958 if Nkind (Parent (N)) /= N_Handled_Sequence_Of_Statements
959 and then
960 (Nkind (Parent (Parent (N))) /= N_Subprogram_Body
961 or else Present (Next (N)))
962 then
963 Check_SPARK_05_Restriction
964 ("RETURN should be the last statement in function", N);
965 end if;
967 else
968 Check_SPARK_05_Restriction ("extended RETURN is not allowed", N);
970 -- Analyze parts specific to extended_return_statement:
972 declare
973 Obj_Decl : constant Node_Id :=
974 Last (Return_Object_Declarations (N));
975 Has_Aliased : constant Boolean := Aliased_Present (Obj_Decl);
976 HSS : constant Node_Id := Handled_Statement_Sequence (N);
978 begin
979 Expr := Expression (Obj_Decl);
981 -- Note: The check for OK_For_Limited_Init will happen in
982 -- Analyze_Object_Declaration; we treat it as a normal
983 -- object declaration.
985 Set_Is_Return_Object (Defining_Identifier (Obj_Decl));
986 Analyze (Obj_Decl);
988 Check_Return_Subtype_Indication (Obj_Decl);
990 if Present (HSS) then
991 Analyze (HSS);
993 if Present (Exception_Handlers (HSS)) then
995 -- ???Has_Nested_Block_With_Handler needs to be set.
996 -- Probably by creating an actual N_Block_Statement.
997 -- Probably in Expand.
999 null;
1000 end if;
1001 end if;
1003 -- Mark the return object as referenced, since the return is an
1004 -- implicit reference of the object.
1006 Set_Referenced (Defining_Identifier (Obj_Decl));
1008 Check_References (Stm_Entity);
1010 -- Check RM 6.5 (5.9/3)
1012 if Has_Aliased then
1013 if Ada_Version < Ada_2012 then
1015 -- Shouldn't this test Warn_On_Ada_2012_Compatibility ???
1016 -- Can it really happen (extended return???)
1018 Error_Msg_N
1019 ("aliased only allowed for limited return objects "
1020 & "in Ada 2012??", N);
1022 elsif not Is_Limited_View (R_Type) then
1023 Error_Msg_N
1024 ("aliased only allowed for limited return objects", N);
1025 end if;
1026 end if;
1027 end;
1028 end if;
1030 -- Case of Expr present
1032 if Present (Expr)
1034 -- Defend against previous errors
1036 and then Nkind (Expr) /= N_Empty
1037 and then Present (Etype (Expr))
1038 then
1039 -- Apply constraint check. Note that this is done before the implicit
1040 -- conversion of the expression done for anonymous access types to
1041 -- ensure correct generation of the null-excluding check associated
1042 -- with null-excluding expressions found in return statements.
1044 Apply_Constraint_Check (Expr, R_Type);
1046 -- Ada 2005 (AI-318-02): When the result type is an anonymous access
1047 -- type, apply an implicit conversion of the expression to that type
1048 -- to force appropriate static and run-time accessibility checks.
1050 if Ada_Version >= Ada_2005
1051 and then Ekind (R_Type) = E_Anonymous_Access_Type
1052 then
1053 Rewrite (Expr, Convert_To (R_Type, Relocate_Node (Expr)));
1054 Analyze_And_Resolve (Expr, R_Type);
1056 -- If this is a local anonymous access to subprogram, the
1057 -- accessibility check can be applied statically. The return is
1058 -- illegal if the access type of the return expression is declared
1059 -- inside of the subprogram (except if it is the subtype indication
1060 -- of an extended return statement).
1062 elsif Ekind (R_Type) = E_Anonymous_Access_Subprogram_Type then
1063 if not Comes_From_Source (Current_Scope)
1064 or else Ekind (Current_Scope) = E_Return_Statement
1065 then
1066 null;
1068 elsif
1069 Scope_Depth (Scope (Etype (Expr))) >= Scope_Depth (Scope_Id)
1070 then
1071 Error_Msg_N ("cannot return local access to subprogram", N);
1072 end if;
1074 -- The expression cannot be of a formal incomplete type
1076 elsif Ekind (Etype (Expr)) = E_Incomplete_Type
1077 and then Is_Generic_Type (Etype (Expr))
1078 then
1079 Error_Msg_N
1080 ("cannot return expression of a formal incomplete type", N);
1081 end if;
1083 -- If the result type is class-wide, then check that the return
1084 -- expression's type is not declared at a deeper level than the
1085 -- function (RM05-6.5(5.6/2)).
1087 if Ada_Version >= Ada_2005
1088 and then Is_Class_Wide_Type (R_Type)
1089 then
1090 if Type_Access_Level (Etype (Expr)) >
1091 Subprogram_Access_Level (Scope_Id)
1092 then
1093 Error_Msg_N
1094 ("level of return expression type is deeper than "
1095 & "class-wide function!", Expr);
1096 end if;
1097 end if;
1099 -- Check incorrect use of dynamically tagged expression
1101 if Is_Tagged_Type (R_Type) then
1102 Check_Dynamically_Tagged_Expression
1103 (Expr => Expr,
1104 Typ => R_Type,
1105 Related_Nod => N);
1106 end if;
1108 -- ??? A real run-time accessibility check is needed in cases
1109 -- involving dereferences of access parameters. For now we just
1110 -- check the static cases.
1112 if (Ada_Version < Ada_2005 or else Debug_Flag_Dot_L)
1113 and then Is_Limited_View (Etype (Scope_Id))
1114 and then Object_Access_Level (Expr) >
1115 Subprogram_Access_Level (Scope_Id)
1116 then
1117 -- Suppress the message in a generic, where the rewriting
1118 -- is irrelevant.
1120 if Inside_A_Generic then
1121 null;
1123 else
1124 Rewrite (N,
1125 Make_Raise_Program_Error (Loc,
1126 Reason => PE_Accessibility_Check_Failed));
1127 Analyze (N);
1129 Error_Msg_Warn := SPARK_Mode /= On;
1130 Error_Msg_N ("cannot return a local value by reference<<", N);
1131 Error_Msg_NE ("\& [<<", N, Standard_Program_Error);
1132 end if;
1133 end if;
1135 if Known_Null (Expr)
1136 and then Nkind (Parent (Scope_Id)) = N_Function_Specification
1137 and then Null_Exclusion_Present (Parent (Scope_Id))
1138 then
1139 Apply_Compile_Time_Constraint_Error
1140 (N => Expr,
1141 Msg => "(Ada 2005) null not allowed for "
1142 & "null-excluding return??",
1143 Reason => CE_Null_Not_Allowed);
1144 end if;
1145 end if;
1146 end Analyze_Function_Return;
1148 -------------------------------------
1149 -- Analyze_Generic_Subprogram_Body --
1150 -------------------------------------
1152 procedure Analyze_Generic_Subprogram_Body
1153 (N : Node_Id;
1154 Gen_Id : Entity_Id)
1156 Gen_Decl : constant Node_Id := Unit_Declaration_Node (Gen_Id);
1157 Kind : constant Entity_Kind := Ekind (Gen_Id);
1158 Body_Id : Entity_Id;
1159 New_N : Node_Id;
1160 Spec : Node_Id;
1162 begin
1163 -- Copy body and disable expansion while analyzing the generic For a
1164 -- stub, do not copy the stub (which would load the proper body), this
1165 -- will be done when the proper body is analyzed.
1167 if Nkind (N) /= N_Subprogram_Body_Stub then
1168 New_N := Copy_Generic_Node (N, Empty, Instantiating => False);
1169 Rewrite (N, New_N);
1170 Start_Generic;
1171 end if;
1173 Spec := Specification (N);
1175 -- Within the body of the generic, the subprogram is callable, and
1176 -- behaves like the corresponding non-generic unit.
1178 Body_Id := Defining_Entity (Spec);
1180 if Kind = E_Generic_Procedure
1181 and then Nkind (Spec) /= N_Procedure_Specification
1182 then
1183 Error_Msg_N ("invalid body for generic procedure ", Body_Id);
1184 return;
1186 elsif Kind = E_Generic_Function
1187 and then Nkind (Spec) /= N_Function_Specification
1188 then
1189 Error_Msg_N ("invalid body for generic function ", Body_Id);
1190 return;
1191 end if;
1193 Set_Corresponding_Body (Gen_Decl, Body_Id);
1195 if Has_Completion (Gen_Id)
1196 and then Nkind (Parent (N)) /= N_Subunit
1197 then
1198 Error_Msg_N ("duplicate generic body", N);
1199 return;
1200 else
1201 Set_Has_Completion (Gen_Id);
1202 end if;
1204 if Nkind (N) = N_Subprogram_Body_Stub then
1205 Set_Ekind (Defining_Entity (Specification (N)), Kind);
1206 else
1207 Set_Corresponding_Spec (N, Gen_Id);
1208 end if;
1210 if Nkind (Parent (N)) = N_Compilation_Unit then
1211 Set_Cunit_Entity (Current_Sem_Unit, Defining_Entity (N));
1212 end if;
1214 -- Make generic parameters immediately visible in the body. They are
1215 -- needed to process the formals declarations. Then make the formals
1216 -- visible in a separate step.
1218 Push_Scope (Gen_Id);
1220 declare
1221 E : Entity_Id;
1222 First_Ent : Entity_Id;
1224 begin
1225 First_Ent := First_Entity (Gen_Id);
1227 E := First_Ent;
1228 while Present (E) and then not Is_Formal (E) loop
1229 Install_Entity (E);
1230 Next_Entity (E);
1231 end loop;
1233 Set_Use (Generic_Formal_Declarations (Gen_Decl));
1235 -- Now generic formals are visible, and the specification can be
1236 -- analyzed, for subsequent conformance check.
1238 Body_Id := Analyze_Subprogram_Specification (Spec);
1240 -- Make formal parameters visible
1242 if Present (E) then
1244 -- E is the first formal parameter, we loop through the formals
1245 -- installing them so that they will be visible.
1247 Set_First_Entity (Gen_Id, E);
1248 while Present (E) loop
1249 Install_Entity (E);
1250 Next_Formal (E);
1251 end loop;
1252 end if;
1254 -- Visible generic entity is callable within its own body
1256 Set_Ekind (Gen_Id, Ekind (Body_Id));
1257 Set_Contract (Body_Id, Make_Contract (Sloc (Body_Id)));
1258 Set_Ekind (Body_Id, E_Subprogram_Body);
1259 Set_Convention (Body_Id, Convention (Gen_Id));
1260 Set_Is_Obsolescent (Body_Id, Is_Obsolescent (Gen_Id));
1261 Set_Scope (Body_Id, Scope (Gen_Id));
1263 -- Inherit the "ghostness" of the generic spec. Note that this
1264 -- property is not directly inherited as the body may be subject
1265 -- to a different Ghost assertion policy.
1267 if Is_Ghost_Entity (Gen_Id) or else Ghost_Mode > None then
1268 Set_Is_Ghost_Entity (Body_Id);
1270 -- The Ghost policy in effect at the point of declaration and at
1271 -- the point of completion must match (SPARK RM 6.9(15)).
1273 Check_Ghost_Completion (Gen_Id, Body_Id);
1274 end if;
1276 Check_Fully_Conformant (Body_Id, Gen_Id, Body_Id);
1278 if Nkind (N) = N_Subprogram_Body_Stub then
1280 -- No body to analyze, so restore state of generic unit
1282 Set_Ekind (Gen_Id, Kind);
1283 Set_Ekind (Body_Id, Kind);
1285 if Present (First_Ent) then
1286 Set_First_Entity (Gen_Id, First_Ent);
1287 end if;
1289 End_Scope;
1290 return;
1291 end if;
1293 -- If this is a compilation unit, it must be made visible explicitly,
1294 -- because the compilation of the declaration, unlike other library
1295 -- unit declarations, does not. If it is not a unit, the following
1296 -- is redundant but harmless.
1298 Set_Is_Immediately_Visible (Gen_Id);
1299 Reference_Body_Formals (Gen_Id, Body_Id);
1301 if Is_Child_Unit (Gen_Id) then
1302 Generate_Reference (Gen_Id, Scope (Gen_Id), 'k', False);
1303 end if;
1305 Set_Actual_Subtypes (N, Current_Scope);
1307 -- Deal with [refined] preconditions, postconditions, Contract_Cases,
1308 -- invariants and predicates associated with the body and its spec.
1309 -- Note that this is not pure expansion as Expand_Subprogram_Contract
1310 -- prepares the contract assertions for generic subprograms or for
1311 -- ASIS. Do not generate contract checks in SPARK mode.
1313 if not GNATprove_Mode then
1314 Expand_Subprogram_Contract (N, Gen_Id, Body_Id);
1315 end if;
1317 -- If the generic unit carries pre- or post-conditions, copy them
1318 -- to the original generic tree, so that they are properly added
1319 -- to any instantiation.
1321 declare
1322 Orig : constant Node_Id := Original_Node (N);
1323 Cond : Node_Id;
1325 begin
1326 Cond := First (Declarations (N));
1327 while Present (Cond) loop
1328 if Nkind (Cond) = N_Pragma
1329 and then Pragma_Name (Cond) = Name_Check
1330 then
1331 Prepend (New_Copy_Tree (Cond), Declarations (Orig));
1333 elsif Nkind (Cond) = N_Pragma
1334 and then Pragma_Name (Cond) = Name_Postcondition
1335 then
1336 Set_Ekind (Defining_Entity (Orig), Ekind (Gen_Id));
1337 Prepend (New_Copy_Tree (Cond), Declarations (Orig));
1338 else
1339 exit;
1340 end if;
1342 Next (Cond);
1343 end loop;
1344 end;
1346 Set_SPARK_Pragma (Body_Id, SPARK_Mode_Pragma);
1347 Set_SPARK_Pragma_Inherited (Body_Id, True);
1349 Analyze_Declarations (Declarations (N));
1350 Check_Completion;
1351 Analyze (Handled_Statement_Sequence (N));
1353 Save_Global_References (Original_Node (N));
1355 -- Prior to exiting the scope, include generic formals again (if any
1356 -- are present) in the set of local entities.
1358 if Present (First_Ent) then
1359 Set_First_Entity (Gen_Id, First_Ent);
1360 end if;
1362 Check_References (Gen_Id);
1363 end;
1365 Process_End_Label (Handled_Statement_Sequence (N), 't', Current_Scope);
1366 End_Scope;
1367 Check_Subprogram_Order (N);
1369 -- Outside of its body, unit is generic again
1371 Set_Ekind (Gen_Id, Kind);
1372 Generate_Reference (Gen_Id, Body_Id, 'b', Set_Ref => False);
1374 if Style_Check then
1375 Style.Check_Identifier (Body_Id, Gen_Id);
1376 end if;
1378 End_Generic;
1379 end Analyze_Generic_Subprogram_Body;
1381 ----------------------------
1382 -- Analyze_Null_Procedure --
1383 ----------------------------
1385 procedure Analyze_Null_Procedure
1386 (N : Node_Id;
1387 Is_Completion : out Boolean)
1389 Loc : constant Source_Ptr := Sloc (N);
1390 Spec : constant Node_Id := Specification (N);
1391 Designator : Entity_Id;
1392 Form : Node_Id;
1393 Null_Body : Node_Id := Empty;
1394 Prev : Entity_Id;
1396 begin
1397 -- Capture the profile of the null procedure before analysis, for
1398 -- expansion at the freeze point and at each point of call. The body is
1399 -- used if the procedure has preconditions, or if it is a completion. In
1400 -- the first case the body is analyzed at the freeze point, in the other
1401 -- it replaces the null procedure declaration.
1403 Null_Body :=
1404 Make_Subprogram_Body (Loc,
1405 Specification => New_Copy_Tree (Spec),
1406 Declarations => New_List,
1407 Handled_Statement_Sequence =>
1408 Make_Handled_Sequence_Of_Statements (Loc,
1409 Statements => New_List (Make_Null_Statement (Loc))));
1411 -- Create new entities for body and formals
1413 Set_Defining_Unit_Name (Specification (Null_Body),
1414 Make_Defining_Identifier
1415 (Sloc (Defining_Entity (N)),
1416 Chars (Defining_Entity (N))));
1418 Form := First (Parameter_Specifications (Specification (Null_Body)));
1419 while Present (Form) loop
1420 Set_Defining_Identifier (Form,
1421 Make_Defining_Identifier
1422 (Sloc (Defining_Identifier (Form)),
1423 Chars (Defining_Identifier (Form))));
1424 Next (Form);
1425 end loop;
1427 -- Determine whether the null procedure may be a completion of a generic
1428 -- suprogram, in which case we use the new null body as the completion
1429 -- and set minimal semantic information on the original declaration,
1430 -- which is rewritten as a null statement.
1432 Prev := Current_Entity_In_Scope (Defining_Entity (Spec));
1434 if Present (Prev) and then Is_Generic_Subprogram (Prev) then
1435 Insert_Before (N, Null_Body);
1436 Set_Ekind (Defining_Entity (N), Ekind (Prev));
1437 Set_Contract (Defining_Entity (N), Make_Contract (Loc));
1439 Rewrite (N, Make_Null_Statement (Loc));
1440 Analyze_Generic_Subprogram_Body (Null_Body, Prev);
1441 Is_Completion := True;
1442 return;
1444 else
1445 -- Resolve the types of the formals now, because the freeze point
1446 -- may appear in a different context, e.g. an instantiation.
1448 Form := First (Parameter_Specifications (Specification (Null_Body)));
1449 while Present (Form) loop
1450 if Nkind (Parameter_Type (Form)) /= N_Access_Definition then
1451 Find_Type (Parameter_Type (Form));
1453 elsif
1454 No (Access_To_Subprogram_Definition (Parameter_Type (Form)))
1455 then
1456 Find_Type (Subtype_Mark (Parameter_Type (Form)));
1458 else
1459 -- The case of a null procedure with a formal that is an
1460 -- access_to_subprogram type, and that is used as an actual
1461 -- in an instantiation is left to the enthusiastic reader.
1463 null;
1464 end if;
1466 Next (Form);
1467 end loop;
1468 end if;
1470 -- If there are previous overloadable entities with the same name,
1471 -- check whether any of them is completed by the null procedure.
1473 if Present (Prev) and then Is_Overloadable (Prev) then
1474 Designator := Analyze_Subprogram_Specification (Spec);
1475 Prev := Find_Corresponding_Spec (N);
1476 end if;
1478 if No (Prev) or else not Comes_From_Source (Prev) then
1479 Designator := Analyze_Subprogram_Specification (Spec);
1480 Set_Has_Completion (Designator);
1482 -- Signal to caller that this is a procedure declaration
1484 Is_Completion := False;
1486 -- Null procedures are always inlined, but generic formal subprograms
1487 -- which appear as such in the internal instance of formal packages,
1488 -- need no completion and are not marked Inline.
1490 if Expander_Active
1491 and then Nkind (N) /= N_Formal_Concrete_Subprogram_Declaration
1492 then
1493 Set_Corresponding_Body (N, Defining_Entity (Null_Body));
1494 Set_Body_To_Inline (N, Null_Body);
1495 Set_Is_Inlined (Designator);
1496 end if;
1498 else
1499 -- The null procedure is a completion. We unconditionally rewrite
1500 -- this as a null body (even if expansion is not active), because
1501 -- there are various error checks that are applied on this body
1502 -- when it is analyzed (e.g. correct aspect placement).
1504 if Has_Completion (Prev) then
1505 Error_Msg_Sloc := Sloc (Prev);
1506 Error_Msg_NE ("duplicate body for & declared#", N, Prev);
1507 end if;
1509 Is_Completion := True;
1510 Rewrite (N, Null_Body);
1511 Analyze (N);
1512 end if;
1513 end Analyze_Null_Procedure;
1515 -----------------------------
1516 -- Analyze_Operator_Symbol --
1517 -----------------------------
1519 -- An operator symbol such as "+" or "and" may appear in context where the
1520 -- literal denotes an entity name, such as "+"(x, y) or in context when it
1521 -- is just a string, as in (conjunction = "or"). In these cases the parser
1522 -- generates this node, and the semantics does the disambiguation. Other
1523 -- such case are actuals in an instantiation, the generic unit in an
1524 -- instantiation, and pragma arguments.
1526 procedure Analyze_Operator_Symbol (N : Node_Id) is
1527 Par : constant Node_Id := Parent (N);
1529 begin
1530 if (Nkind (Par) = N_Function_Call and then N = Name (Par))
1531 or else Nkind (Par) = N_Function_Instantiation
1532 or else (Nkind (Par) = N_Indexed_Component and then N = Prefix (Par))
1533 or else (Nkind (Par) = N_Pragma_Argument_Association
1534 and then not Is_Pragma_String_Literal (Par))
1535 or else Nkind (Par) = N_Subprogram_Renaming_Declaration
1536 or else (Nkind (Par) = N_Attribute_Reference
1537 and then Attribute_Name (Par) /= Name_Value)
1538 then
1539 Find_Direct_Name (N);
1541 else
1542 Change_Operator_Symbol_To_String_Literal (N);
1543 Analyze (N);
1544 end if;
1545 end Analyze_Operator_Symbol;
1547 -----------------------------------
1548 -- Analyze_Parameter_Association --
1549 -----------------------------------
1551 procedure Analyze_Parameter_Association (N : Node_Id) is
1552 begin
1553 Analyze (Explicit_Actual_Parameter (N));
1554 end Analyze_Parameter_Association;
1556 ----------------------------
1557 -- Analyze_Procedure_Call --
1558 ----------------------------
1560 procedure Analyze_Procedure_Call (N : Node_Id) is
1561 Loc : constant Source_Ptr := Sloc (N);
1562 P : constant Node_Id := Name (N);
1563 Actuals : constant List_Id := Parameter_Associations (N);
1564 Actual : Node_Id;
1565 New_N : Node_Id;
1567 procedure Analyze_Call_And_Resolve;
1568 -- Do Analyze and Resolve calls for procedure call
1569 -- At end, check illegal order dependence.
1571 ------------------------------
1572 -- Analyze_Call_And_Resolve --
1573 ------------------------------
1575 procedure Analyze_Call_And_Resolve is
1576 begin
1577 if Nkind (N) = N_Procedure_Call_Statement then
1578 Analyze_Call (N);
1579 Resolve (N, Standard_Void_Type);
1580 else
1581 Analyze (N);
1582 end if;
1583 end Analyze_Call_And_Resolve;
1585 -- Start of processing for Analyze_Procedure_Call
1587 begin
1588 -- The syntactic construct: PREFIX ACTUAL_PARAMETER_PART can denote
1589 -- a procedure call or an entry call. The prefix may denote an access
1590 -- to subprogram type, in which case an implicit dereference applies.
1591 -- If the prefix is an indexed component (without implicit dereference)
1592 -- then the construct denotes a call to a member of an entire family.
1593 -- If the prefix is a simple name, it may still denote a call to a
1594 -- parameterless member of an entry family. Resolution of these various
1595 -- interpretations is delicate.
1597 Analyze (P);
1599 -- If this is a call of the form Obj.Op, the call may have been
1600 -- analyzed and possibly rewritten into a block, in which case
1601 -- we are done.
1603 if Analyzed (N) then
1604 return;
1605 end if;
1607 -- If there is an error analyzing the name (which may have been
1608 -- rewritten if the original call was in prefix notation) then error
1609 -- has been emitted already, mark node and return.
1611 if Error_Posted (N) or else Etype (Name (N)) = Any_Type then
1612 Set_Etype (N, Any_Type);
1613 return;
1614 end if;
1616 -- The name of the procedure call may reference an entity subject to
1617 -- pragma Ghost with policy Ignore. Set the mode now to ensure that any
1618 -- nodes generated during analysis and expansion are properly flagged as
1619 -- ignored Ghost.
1621 Set_Ghost_Mode (N);
1623 -- Otherwise analyze the parameters
1625 if Present (Actuals) then
1626 Actual := First (Actuals);
1628 while Present (Actual) loop
1629 Analyze (Actual);
1630 Check_Parameterless_Call (Actual);
1631 Next (Actual);
1632 end loop;
1633 end if;
1635 -- Special processing for Elab_Spec, Elab_Body and Elab_Subp_Body calls
1637 if Nkind (P) = N_Attribute_Reference
1638 and then Nam_In (Attribute_Name (P), Name_Elab_Spec,
1639 Name_Elab_Body,
1640 Name_Elab_Subp_Body)
1641 then
1642 if Present (Actuals) then
1643 Error_Msg_N
1644 ("no parameters allowed for this call", First (Actuals));
1645 return;
1646 end if;
1648 Set_Etype (N, Standard_Void_Type);
1649 Set_Analyzed (N);
1651 elsif Is_Entity_Name (P)
1652 and then Is_Record_Type (Etype (Entity (P)))
1653 and then Remote_AST_I_Dereference (P)
1654 then
1655 return;
1657 elsif Is_Entity_Name (P)
1658 and then Ekind (Entity (P)) /= E_Entry_Family
1659 then
1660 if Is_Access_Type (Etype (P))
1661 and then Ekind (Designated_Type (Etype (P))) = E_Subprogram_Type
1662 and then No (Actuals)
1663 and then Comes_From_Source (N)
1664 then
1665 Error_Msg_N ("missing explicit dereference in call", N);
1666 end if;
1668 Analyze_Call_And_Resolve;
1670 -- If the prefix is the simple name of an entry family, this is
1671 -- a parameterless call from within the task body itself.
1673 elsif Is_Entity_Name (P)
1674 and then Nkind (P) = N_Identifier
1675 and then Ekind (Entity (P)) = E_Entry_Family
1676 and then Present (Actuals)
1677 and then No (Next (First (Actuals)))
1678 then
1679 -- Can be call to parameterless entry family. What appears to be the
1680 -- sole argument is in fact the entry index. Rewrite prefix of node
1681 -- accordingly. Source representation is unchanged by this
1682 -- transformation.
1684 New_N :=
1685 Make_Indexed_Component (Loc,
1686 Prefix =>
1687 Make_Selected_Component (Loc,
1688 Prefix => New_Occurrence_Of (Scope (Entity (P)), Loc),
1689 Selector_Name => New_Occurrence_Of (Entity (P), Loc)),
1690 Expressions => Actuals);
1691 Set_Name (N, New_N);
1692 Set_Etype (New_N, Standard_Void_Type);
1693 Set_Parameter_Associations (N, No_List);
1694 Analyze_Call_And_Resolve;
1696 elsif Nkind (P) = N_Explicit_Dereference then
1697 if Ekind (Etype (P)) = E_Subprogram_Type then
1698 Analyze_Call_And_Resolve;
1699 else
1700 Error_Msg_N ("expect access to procedure in call", P);
1701 end if;
1703 -- The name can be a selected component or an indexed component that
1704 -- yields an access to subprogram. Such a prefix is legal if the call
1705 -- has parameter associations.
1707 elsif Is_Access_Type (Etype (P))
1708 and then Ekind (Designated_Type (Etype (P))) = E_Subprogram_Type
1709 then
1710 if Present (Actuals) then
1711 Analyze_Call_And_Resolve;
1712 else
1713 Error_Msg_N ("missing explicit dereference in call ", N);
1714 end if;
1716 -- If not an access to subprogram, then the prefix must resolve to the
1717 -- name of an entry, entry family, or protected operation.
1719 -- For the case of a simple entry call, P is a selected component where
1720 -- the prefix is the task and the selector name is the entry. A call to
1721 -- a protected procedure will have the same syntax. If the protected
1722 -- object contains overloaded operations, the entity may appear as a
1723 -- function, the context will select the operation whose type is Void.
1725 elsif Nkind (P) = N_Selected_Component
1726 and then Ekind_In (Entity (Selector_Name (P)), E_Entry,
1727 E_Procedure,
1728 E_Function)
1729 then
1730 Analyze_Call_And_Resolve;
1732 elsif Nkind (P) = N_Selected_Component
1733 and then Ekind (Entity (Selector_Name (P))) = E_Entry_Family
1734 and then Present (Actuals)
1735 and then No (Next (First (Actuals)))
1736 then
1737 -- Can be call to parameterless entry family. What appears to be the
1738 -- sole argument is in fact the entry index. Rewrite prefix of node
1739 -- accordingly. Source representation is unchanged by this
1740 -- transformation.
1742 New_N :=
1743 Make_Indexed_Component (Loc,
1744 Prefix => New_Copy (P),
1745 Expressions => Actuals);
1746 Set_Name (N, New_N);
1747 Set_Etype (New_N, Standard_Void_Type);
1748 Set_Parameter_Associations (N, No_List);
1749 Analyze_Call_And_Resolve;
1751 -- For the case of a reference to an element of an entry family, P is
1752 -- an indexed component whose prefix is a selected component (task and
1753 -- entry family), and whose index is the entry family index.
1755 elsif Nkind (P) = N_Indexed_Component
1756 and then Nkind (Prefix (P)) = N_Selected_Component
1757 and then Ekind (Entity (Selector_Name (Prefix (P)))) = E_Entry_Family
1758 then
1759 Analyze_Call_And_Resolve;
1761 -- If the prefix is the name of an entry family, it is a call from
1762 -- within the task body itself.
1764 elsif Nkind (P) = N_Indexed_Component
1765 and then Nkind (Prefix (P)) = N_Identifier
1766 and then Ekind (Entity (Prefix (P))) = E_Entry_Family
1767 then
1768 New_N :=
1769 Make_Selected_Component (Loc,
1770 Prefix => New_Occurrence_Of (Scope (Entity (Prefix (P))), Loc),
1771 Selector_Name => New_Occurrence_Of (Entity (Prefix (P)), Loc));
1772 Rewrite (Prefix (P), New_N);
1773 Analyze (P);
1774 Analyze_Call_And_Resolve;
1776 -- In Ada 2012. a qualified expression is a name, but it cannot be a
1777 -- procedure name, so the construct can only be a qualified expression.
1779 elsif Nkind (P) = N_Qualified_Expression
1780 and then Ada_Version >= Ada_2012
1781 then
1782 Rewrite (N, Make_Code_Statement (Loc, Expression => P));
1783 Analyze (N);
1785 -- Anything else is an error
1787 else
1788 Error_Msg_N ("invalid procedure or entry call", N);
1789 end if;
1790 end Analyze_Procedure_Call;
1792 ------------------------------
1793 -- Analyze_Return_Statement --
1794 ------------------------------
1796 procedure Analyze_Return_Statement (N : Node_Id) is
1798 pragma Assert (Nkind_In (N, N_Simple_Return_Statement,
1799 N_Extended_Return_Statement));
1801 Returns_Object : constant Boolean :=
1802 Nkind (N) = N_Extended_Return_Statement
1803 or else
1804 (Nkind (N) = N_Simple_Return_Statement
1805 and then Present (Expression (N)));
1806 -- True if we're returning something; that is, "return <expression>;"
1807 -- or "return Result : T [:= ...]". False for "return;". Used for error
1808 -- checking: If Returns_Object is True, N should apply to a function
1809 -- body; otherwise N should apply to a procedure body, entry body,
1810 -- accept statement, or extended return statement.
1812 function Find_What_It_Applies_To return Entity_Id;
1813 -- Find the entity representing the innermost enclosing body, accept
1814 -- statement, or extended return statement. If the result is a callable
1815 -- construct or extended return statement, then this will be the value
1816 -- of the Return_Applies_To attribute. Otherwise, the program is
1817 -- illegal. See RM-6.5(4/2).
1819 -----------------------------
1820 -- Find_What_It_Applies_To --
1821 -----------------------------
1823 function Find_What_It_Applies_To return Entity_Id is
1824 Result : Entity_Id := Empty;
1826 begin
1827 -- Loop outward through the Scope_Stack, skipping blocks, loops,
1828 -- and postconditions.
1830 for J in reverse 0 .. Scope_Stack.Last loop
1831 Result := Scope_Stack.Table (J).Entity;
1832 exit when not Ekind_In (Result, E_Block, E_Loop)
1833 and then Chars (Result) /= Name_uPostconditions;
1834 end loop;
1836 pragma Assert (Present (Result));
1837 return Result;
1838 end Find_What_It_Applies_To;
1840 -- Local declarations
1842 Scope_Id : constant Entity_Id := Find_What_It_Applies_To;
1843 Kind : constant Entity_Kind := Ekind (Scope_Id);
1844 Loc : constant Source_Ptr := Sloc (N);
1845 Stm_Entity : constant Entity_Id :=
1846 New_Internal_Entity
1847 (E_Return_Statement, Current_Scope, Loc, 'R');
1849 -- Start of processing for Analyze_Return_Statement
1851 begin
1852 Set_Return_Statement_Entity (N, Stm_Entity);
1854 Set_Etype (Stm_Entity, Standard_Void_Type);
1855 Set_Return_Applies_To (Stm_Entity, Scope_Id);
1857 -- Place Return entity on scope stack, to simplify enforcement of 6.5
1858 -- (4/2): an inner return statement will apply to this extended return.
1860 if Nkind (N) = N_Extended_Return_Statement then
1861 Push_Scope (Stm_Entity);
1862 end if;
1864 -- Check that pragma No_Return is obeyed. Don't complain about the
1865 -- implicitly-generated return that is placed at the end.
1867 if No_Return (Scope_Id) and then Comes_From_Source (N) then
1868 Error_Msg_N ("RETURN statement not allowed (No_Return)", N);
1869 end if;
1871 -- Warn on any unassigned OUT parameters if in procedure
1873 if Ekind (Scope_Id) = E_Procedure then
1874 Warn_On_Unassigned_Out_Parameter (N, Scope_Id);
1875 end if;
1877 -- Check that functions return objects, and other things do not
1879 if Kind = E_Function or else Kind = E_Generic_Function then
1880 if not Returns_Object then
1881 Error_Msg_N ("missing expression in return from function", N);
1882 end if;
1884 elsif Kind = E_Procedure or else Kind = E_Generic_Procedure then
1885 if Returns_Object then
1886 Error_Msg_N ("procedure cannot return value (use function)", N);
1887 end if;
1889 elsif Kind = E_Entry or else Kind = E_Entry_Family then
1890 if Returns_Object then
1891 if Is_Protected_Type (Scope (Scope_Id)) then
1892 Error_Msg_N ("entry body cannot return value", N);
1893 else
1894 Error_Msg_N ("accept statement cannot return value", N);
1895 end if;
1896 end if;
1898 elsif Kind = E_Return_Statement then
1900 -- We are nested within another return statement, which must be an
1901 -- extended_return_statement.
1903 if Returns_Object then
1904 if Nkind (N) = N_Extended_Return_Statement then
1905 Error_Msg_N
1906 ("extended return statement cannot be nested (use `RETURN;`)",
1909 -- Case of a simple return statement with a value inside extended
1910 -- return statement.
1912 else
1913 Error_Msg_N
1914 ("return nested in extended return statement cannot return "
1915 & "value (use `RETURN;`)", N);
1916 end if;
1917 end if;
1919 else
1920 Error_Msg_N ("illegal context for return statement", N);
1921 end if;
1923 if Ekind_In (Kind, E_Function, E_Generic_Function) then
1924 Analyze_Function_Return (N);
1926 elsif Ekind_In (Kind, E_Procedure, E_Generic_Procedure) then
1927 Set_Return_Present (Scope_Id);
1928 end if;
1930 if Nkind (N) = N_Extended_Return_Statement then
1931 End_Scope;
1932 end if;
1934 Kill_Current_Values (Last_Assignment_Only => True);
1935 Check_Unreachable_Code (N);
1937 Analyze_Dimension (N);
1938 end Analyze_Return_Statement;
1940 -------------------------------------
1941 -- Analyze_Simple_Return_Statement --
1942 -------------------------------------
1944 procedure Analyze_Simple_Return_Statement (N : Node_Id) is
1945 begin
1946 if Present (Expression (N)) then
1947 Mark_Coextensions (N, Expression (N));
1948 end if;
1950 Analyze_Return_Statement (N);
1951 end Analyze_Simple_Return_Statement;
1953 -------------------------
1954 -- Analyze_Return_Type --
1955 -------------------------
1957 procedure Analyze_Return_Type (N : Node_Id) is
1958 Designator : constant Entity_Id := Defining_Entity (N);
1959 Typ : Entity_Id := Empty;
1961 begin
1962 -- Normal case where result definition does not indicate an error
1964 if Result_Definition (N) /= Error then
1965 if Nkind (Result_Definition (N)) = N_Access_Definition then
1966 Check_SPARK_05_Restriction
1967 ("access result is not allowed", Result_Definition (N));
1969 -- Ada 2005 (AI-254): Handle anonymous access to subprograms
1971 declare
1972 AD : constant Node_Id :=
1973 Access_To_Subprogram_Definition (Result_Definition (N));
1974 begin
1975 if Present (AD) and then Protected_Present (AD) then
1976 Typ := Replace_Anonymous_Access_To_Protected_Subprogram (N);
1977 else
1978 Typ := Access_Definition (N, Result_Definition (N));
1979 end if;
1980 end;
1982 Set_Parent (Typ, Result_Definition (N));
1983 Set_Is_Local_Anonymous_Access (Typ);
1984 Set_Etype (Designator, Typ);
1986 -- Ada 2005 (AI-231): Ensure proper usage of null exclusion
1988 Null_Exclusion_Static_Checks (N);
1990 -- Subtype_Mark case
1992 else
1993 Find_Type (Result_Definition (N));
1994 Typ := Entity (Result_Definition (N));
1995 Set_Etype (Designator, Typ);
1997 -- Unconstrained array as result is not allowed in SPARK
1999 if Is_Array_Type (Typ) and then not Is_Constrained (Typ) then
2000 Check_SPARK_05_Restriction
2001 ("returning an unconstrained array is not allowed",
2002 Result_Definition (N));
2003 end if;
2005 -- Ada 2005 (AI-231): Ensure proper usage of null exclusion
2007 Null_Exclusion_Static_Checks (N);
2009 -- If a null exclusion is imposed on the result type, then create
2010 -- a null-excluding itype (an access subtype) and use it as the
2011 -- function's Etype. Note that the null exclusion checks are done
2012 -- right before this, because they don't get applied to types that
2013 -- do not come from source.
2015 if Is_Access_Type (Typ) and then Null_Exclusion_Present (N) then
2016 Set_Etype (Designator,
2017 Create_Null_Excluding_Itype
2018 (T => Typ,
2019 Related_Nod => N,
2020 Scope_Id => Scope (Current_Scope)));
2022 -- The new subtype must be elaborated before use because
2023 -- it is visible outside of the function. However its base
2024 -- type may not be frozen yet, so the reference that will
2025 -- force elaboration must be attached to the freezing of
2026 -- the base type.
2028 -- If the return specification appears on a proper body,
2029 -- the subtype will have been created already on the spec.
2031 if Is_Frozen (Typ) then
2032 if Nkind (Parent (N)) = N_Subprogram_Body
2033 and then Nkind (Parent (Parent (N))) = N_Subunit
2034 then
2035 null;
2036 else
2037 Build_Itype_Reference (Etype (Designator), Parent (N));
2038 end if;
2040 else
2041 Ensure_Freeze_Node (Typ);
2043 declare
2044 IR : constant Node_Id := Make_Itype_Reference (Sloc (N));
2045 begin
2046 Set_Itype (IR, Etype (Designator));
2047 Append_Freeze_Actions (Typ, New_List (IR));
2048 end;
2049 end if;
2051 else
2052 Set_Etype (Designator, Typ);
2053 end if;
2055 if Ekind (Typ) = E_Incomplete_Type
2056 and then Is_Value_Type (Typ)
2057 then
2058 null;
2060 elsif Ekind (Typ) = E_Incomplete_Type
2061 or else (Is_Class_Wide_Type (Typ)
2062 and then Ekind (Root_Type (Typ)) = E_Incomplete_Type)
2063 then
2064 -- AI05-0151: Tagged incomplete types are allowed in all formal
2065 -- parts. Untagged incomplete types are not allowed in bodies.
2066 -- As a consequence, limited views cannot appear in a basic
2067 -- declaration that is itself within a body, because there is
2068 -- no point at which the non-limited view will become visible.
2070 if Ada_Version >= Ada_2012 then
2071 if From_Limited_With (Typ) and then In_Package_Body then
2072 Error_Msg_NE
2073 ("invalid use of incomplete type&",
2074 Result_Definition (N), Typ);
2076 -- The return type of a subprogram body cannot be of a
2077 -- formal incomplete type.
2079 elsif Is_Generic_Type (Typ)
2080 and then Nkind (Parent (N)) = N_Subprogram_Body
2081 then
2082 Error_Msg_N
2083 ("return type cannot be a formal incomplete type",
2084 Result_Definition (N));
2086 elsif Is_Class_Wide_Type (Typ)
2087 and then Is_Generic_Type (Root_Type (Typ))
2088 and then Nkind (Parent (N)) = N_Subprogram_Body
2089 then
2090 Error_Msg_N
2091 ("return type cannot be a formal incomplete type",
2092 Result_Definition (N));
2094 elsif Is_Tagged_Type (Typ) then
2095 null;
2097 -- Use is legal in a thunk generated for an operation
2098 -- inherited from a progenitor.
2100 elsif Is_Thunk (Designator)
2101 and then Present (Non_Limited_View (Typ))
2102 then
2103 null;
2105 elsif Nkind (Parent (N)) = N_Subprogram_Body
2106 or else Nkind_In (Parent (Parent (N)), N_Accept_Statement,
2107 N_Entry_Body)
2108 then
2109 Error_Msg_NE
2110 ("invalid use of untagged incomplete type&",
2111 Designator, Typ);
2112 end if;
2114 -- The type must be completed in the current package. This
2115 -- is checked at the end of the package declaration when
2116 -- Taft-amendment types are identified. If the return type
2117 -- is class-wide, there is no required check, the type can
2118 -- be a bona fide TAT.
2120 if Ekind (Scope (Current_Scope)) = E_Package
2121 and then In_Private_Part (Scope (Current_Scope))
2122 and then not Is_Class_Wide_Type (Typ)
2123 then
2124 Append_Elmt (Designator, Private_Dependents (Typ));
2125 end if;
2127 else
2128 Error_Msg_NE
2129 ("invalid use of incomplete type&", Designator, Typ);
2130 end if;
2131 end if;
2132 end if;
2134 -- Case where result definition does indicate an error
2136 else
2137 Set_Etype (Designator, Any_Type);
2138 end if;
2139 end Analyze_Return_Type;
2141 -----------------------------
2142 -- Analyze_Subprogram_Body --
2143 -----------------------------
2145 procedure Analyze_Subprogram_Body (N : Node_Id) is
2146 Loc : constant Source_Ptr := Sloc (N);
2147 Body_Spec : constant Node_Id := Specification (N);
2148 Body_Id : constant Entity_Id := Defining_Entity (Body_Spec);
2150 begin
2151 if Debug_Flag_C then
2152 Write_Str ("==> subprogram body ");
2153 Write_Name (Chars (Body_Id));
2154 Write_Str (" from ");
2155 Write_Location (Loc);
2156 Write_Eol;
2157 Indent;
2158 end if;
2160 Trace_Scope (N, Body_Id, " Analyze subprogram: ");
2162 -- The real work is split out into the helper, so it can do "return;"
2163 -- without skipping the debug output:
2165 Analyze_Subprogram_Body_Helper (N);
2167 if Debug_Flag_C then
2168 Outdent;
2169 Write_Str ("<== subprogram body ");
2170 Write_Name (Chars (Body_Id));
2171 Write_Str (" from ");
2172 Write_Location (Loc);
2173 Write_Eol;
2174 end if;
2175 end Analyze_Subprogram_Body;
2177 --------------------------------------
2178 -- Analyze_Subprogram_Body_Contract --
2179 --------------------------------------
2181 procedure Analyze_Subprogram_Body_Contract (Body_Id : Entity_Id) is
2182 Body_Decl : constant Node_Id := Parent (Parent (Body_Id));
2183 Mode : SPARK_Mode_Type;
2184 Prag : Node_Id;
2185 Ref_Depends : Node_Id := Empty;
2186 Ref_Global : Node_Id := Empty;
2187 Spec_Id : Entity_Id;
2189 begin
2190 -- Due to the timing of contract analysis, delayed pragmas may be
2191 -- subject to the wrong SPARK_Mode, usually that of the enclosing
2192 -- context. To remedy this, restore the original SPARK_Mode of the
2193 -- related subprogram body.
2195 Save_SPARK_Mode_And_Set (Body_Id, Mode);
2197 -- When a subprogram body declaration is illegal, its defining entity is
2198 -- left unanalyzed. There is nothing left to do in this case because the
2199 -- body lacks a contract, or even a proper Ekind.
2201 if Ekind (Body_Id) = E_Void then
2202 return;
2203 end if;
2205 if Nkind (Body_Decl) = N_Subprogram_Body_Stub then
2206 Spec_Id := Corresponding_Spec_Of_Stub (Body_Decl);
2207 else
2208 Spec_Id := Corresponding_Spec (Body_Decl);
2209 end if;
2211 -- Locate and store pragmas Refined_Depends and Refined_Global since
2212 -- their order of analysis matters.
2214 Prag := Classifications (Contract (Body_Id));
2215 while Present (Prag) loop
2216 if Pragma_Name (Prag) = Name_Refined_Depends then
2217 Ref_Depends := Prag;
2218 elsif Pragma_Name (Prag) = Name_Refined_Global then
2219 Ref_Global := Prag;
2220 end if;
2222 Prag := Next_Pragma (Prag);
2223 end loop;
2225 -- Analyze Refined_Global first as Refined_Depends may mention items
2226 -- classified in the global refinement.
2228 if Present (Ref_Global) then
2229 Analyze_Refined_Global_In_Decl_Part (Ref_Global);
2231 -- When the corresponding Global aspect/pragma references a state with
2232 -- visible refinement, the body requires Refined_Global. Refinement is
2233 -- not required when SPARK checks are suppressed.
2235 elsif Present (Spec_Id) then
2236 Prag := Get_Pragma (Spec_Id, Pragma_Global);
2238 if SPARK_Mode /= Off
2239 and then Present (Prag)
2240 and then Contains_Refined_State (Prag)
2241 then
2242 Error_Msg_NE
2243 ("body of subprogram& requires global refinement",
2244 Body_Decl, Spec_Id);
2245 end if;
2246 end if;
2248 -- Refined_Depends must be analyzed after Refined_Global in order to see
2249 -- the modes of all global refinements.
2251 if Present (Ref_Depends) then
2252 Analyze_Refined_Depends_In_Decl_Part (Ref_Depends);
2254 -- When the corresponding Depends aspect/pragma references a state with
2255 -- visible refinement, the body requires Refined_Depends. Refinement is
2256 -- not required when SPARK checks are suppressed.
2258 elsif Present (Spec_Id) then
2259 Prag := Get_Pragma (Spec_Id, Pragma_Depends);
2261 if SPARK_Mode /= Off
2262 and then Present (Prag)
2263 and then Contains_Refined_State (Prag)
2264 then
2265 Error_Msg_NE
2266 ("body of subprogram& requires dependance refinement",
2267 Body_Decl, Spec_Id);
2268 end if;
2269 end if;
2271 -- Restore the SPARK_Mode of the enclosing context after all delayed
2272 -- pragmas have been analyzed.
2274 Restore_SPARK_Mode (Mode);
2275 end Analyze_Subprogram_Body_Contract;
2277 ------------------------------------
2278 -- Analyze_Subprogram_Body_Helper --
2279 ------------------------------------
2281 -- This procedure is called for regular subprogram bodies, generic bodies,
2282 -- and for subprogram stubs of both kinds. In the case of stubs, only the
2283 -- specification matters, and is used to create a proper declaration for
2284 -- the subprogram, or to perform conformance checks.
2286 procedure Analyze_Subprogram_Body_Helper (N : Node_Id) is
2287 Loc : constant Source_Ptr := Sloc (N);
2288 Body_Spec : constant Node_Id := Specification (N);
2289 Body_Id : Entity_Id := Defining_Entity (Body_Spec);
2290 Prev_Id : constant Entity_Id := Current_Entity_In_Scope (Body_Id);
2291 Conformant : Boolean;
2292 HSS : Node_Id;
2293 Prot_Typ : Entity_Id := Empty;
2294 Spec_Id : Entity_Id;
2295 Spec_Decl : Node_Id := Empty;
2297 Last_Real_Spec_Entity : Entity_Id := Empty;
2298 -- When we analyze a separate spec, the entity chain ends up containing
2299 -- the formals, as well as any itypes generated during analysis of the
2300 -- default expressions for parameters, or the arguments of associated
2301 -- precondition/postcondition pragmas (which are analyzed in the context
2302 -- of the spec since they have visibility on formals).
2304 -- These entities belong with the spec and not the body. However we do
2305 -- the analysis of the body in the context of the spec (again to obtain
2306 -- visibility to the formals), and all the entities generated during
2307 -- this analysis end up also chained to the entity chain of the spec.
2308 -- But they really belong to the body, and there is circuitry to move
2309 -- them from the spec to the body.
2311 -- However, when we do this move, we don't want to move the real spec
2312 -- entities (first para above) to the body. The Last_Real_Spec_Entity
2313 -- variable points to the last real spec entity, so we only move those
2314 -- chained beyond that point. It is initialized to Empty to deal with
2315 -- the case where there is no separate spec.
2317 procedure Analyze_Aspects_On_Body_Or_Stub;
2318 -- Analyze the aspect specifications of a subprogram body [stub]. It is
2319 -- assumed that N has aspects.
2321 function Body_Has_Contract return Boolean;
2322 -- Check whether unanalyzed body has an aspect or pragma that may
2323 -- generate a SPARK contract.
2325 procedure Check_Anonymous_Return;
2326 -- Ada 2005: if a function returns an access type that denotes a task,
2327 -- or a type that contains tasks, we must create a master entity for
2328 -- the anonymous type, which typically will be used in an allocator
2329 -- in the body of the function.
2331 procedure Check_Inline_Pragma (Spec : in out Node_Id);
2332 -- Look ahead to recognize a pragma that may appear after the body.
2333 -- If there is a previous spec, check that it appears in the same
2334 -- declarative part. If the pragma is Inline_Always, perform inlining
2335 -- unconditionally, otherwise only if Front_End_Inlining is requested.
2336 -- If the body acts as a spec, and inlining is required, we create a
2337 -- subprogram declaration for it, in order to attach the body to inline.
2338 -- If pragma does not appear after the body, check whether there is
2339 -- an inline pragma before any local declarations.
2341 procedure Check_Missing_Return;
2342 -- Checks for a function with a no return statements, and also performs
2343 -- the warning checks implemented by Check_Returns. In formal mode, also
2344 -- verify that a function ends with a RETURN and that a procedure does
2345 -- not contain any RETURN.
2347 function Disambiguate_Spec return Entity_Id;
2348 -- When a primitive is declared between the private view and the full
2349 -- view of a concurrent type which implements an interface, a special
2350 -- mechanism is used to find the corresponding spec of the primitive
2351 -- body.
2353 procedure Exchange_Limited_Views (Subp_Id : Entity_Id);
2354 -- Ada 2012 (AI05-0151): Detect whether the profile of Subp_Id contains
2355 -- incomplete types coming from a limited context and swap their limited
2356 -- views with the non-limited ones.
2358 function Is_Private_Concurrent_Primitive
2359 (Subp_Id : Entity_Id) return Boolean;
2360 -- Determine whether subprogram Subp_Id is a primitive of a concurrent
2361 -- type that implements an interface and has a private view.
2363 procedure Set_Trivial_Subprogram (N : Node_Id);
2364 -- Sets the Is_Trivial_Subprogram flag in both spec and body of the
2365 -- subprogram whose body is being analyzed. N is the statement node
2366 -- causing the flag to be set, if the following statement is a return
2367 -- of an entity, we mark the entity as set in source to suppress any
2368 -- warning on the stylized use of function stubs with a dummy return.
2370 procedure Verify_Overriding_Indicator;
2371 -- If there was a previous spec, the entity has been entered in the
2372 -- current scope previously. If the body itself carries an overriding
2373 -- indicator, check that it is consistent with the known status of the
2374 -- entity.
2376 -------------------------------------
2377 -- Analyze_Aspects_On_Body_Or_Stub --
2378 -------------------------------------
2380 procedure Analyze_Aspects_On_Body_Or_Stub is
2381 procedure Diagnose_Misplaced_Aspects;
2382 -- Subprogram body [stub] N has aspects, but they are not properly
2383 -- placed. Provide precise diagnostics depending on the aspects
2384 -- involved.
2386 --------------------------------
2387 -- Diagnose_Misplaced_Aspects --
2388 --------------------------------
2390 procedure Diagnose_Misplaced_Aspects is
2391 Asp : Node_Id;
2392 Asp_Nam : Name_Id;
2393 Asp_Id : Aspect_Id;
2394 -- The current aspect along with its name and id
2396 procedure SPARK_Aspect_Error (Ref_Nam : Name_Id);
2397 -- Emit an error message concerning SPARK aspect Asp. Ref_Nam is
2398 -- the name of the refined version of the aspect.
2400 ------------------------
2401 -- SPARK_Aspect_Error --
2402 ------------------------
2404 procedure SPARK_Aspect_Error (Ref_Nam : Name_Id) is
2405 begin
2406 -- The corresponding spec already contains the aspect in
2407 -- question and the one appearing on the body must be the
2408 -- refined form:
2410 -- procedure P with Global ...;
2411 -- procedure P with Global ... is ... end P;
2412 -- ^
2413 -- Refined_Global
2415 if Has_Aspect (Spec_Id, Asp_Id) then
2416 Error_Msg_Name_1 := Asp_Nam;
2418 -- Subunits cannot carry aspects that apply to a subprogram
2419 -- declaration.
2421 if Nkind (Parent (N)) = N_Subunit then
2422 Error_Msg_N ("aspect % cannot apply to a subunit", Asp);
2424 else
2425 Error_Msg_Name_2 := Ref_Nam;
2426 Error_Msg_N ("aspect % should be %", Asp);
2427 end if;
2429 -- Otherwise the aspect must appear in the spec, not in the
2430 -- body:
2432 -- procedure P;
2433 -- procedure P with Global ... is ... end P;
2435 else
2436 Error_Msg_N
2437 ("aspect specification must appear in subprogram "
2438 & "declaration", Asp);
2439 end if;
2440 end SPARK_Aspect_Error;
2442 -- Start of processing for Diagnose_Misplaced_Aspects
2444 begin
2445 -- Iterate over the aspect specifications and emit specific errors
2446 -- where applicable.
2448 Asp := First (Aspect_Specifications (N));
2449 while Present (Asp) loop
2450 Asp_Nam := Chars (Identifier (Asp));
2451 Asp_Id := Get_Aspect_Id (Asp_Nam);
2453 -- Do not emit errors on aspects that can appear on a
2454 -- subprogram body. This scenario occurs when the aspect
2455 -- specification list contains both misplaced and properly
2456 -- placed aspects.
2458 if Aspect_On_Body_Or_Stub_OK (Asp_Id) then
2459 null;
2461 -- Special diagnostics for SPARK aspects
2463 elsif Asp_Nam = Name_Depends then
2464 SPARK_Aspect_Error (Name_Refined_Depends);
2466 elsif Asp_Nam = Name_Global then
2467 SPARK_Aspect_Error (Name_Refined_Global);
2469 elsif Asp_Nam = Name_Post then
2470 SPARK_Aspect_Error (Name_Refined_Post);
2472 else
2473 Error_Msg_N
2474 ("aspect specification must appear in subprogram "
2475 & "declaration", Asp);
2476 end if;
2478 Next (Asp);
2479 end loop;
2480 end Diagnose_Misplaced_Aspects;
2482 -- Start of processing for Analyze_Aspects_On_Body_Or_Stub
2484 begin
2485 -- Language-defined aspects cannot be associated with a subprogram
2486 -- body [stub] if the subprogram has a spec. Certain implementation
2487 -- defined aspects are allowed to break this rule (for list, see
2488 -- table Aspect_On_Body_Or_Stub_OK).
2490 if Present (Spec_Id) and then not Aspects_On_Body_Or_Stub_OK (N) then
2491 Diagnose_Misplaced_Aspects;
2492 else
2493 Analyze_Aspect_Specifications (N, Body_Id);
2494 end if;
2495 end Analyze_Aspects_On_Body_Or_Stub;
2497 -----------------------
2498 -- Body_Has_Contract --
2499 -----------------------
2501 function Body_Has_Contract return Boolean is
2502 Decls : constant List_Id := Declarations (N);
2503 A_Spec : Node_Id;
2504 A : Aspect_Id;
2505 Decl : Node_Id;
2506 P_Id : Pragma_Id;
2508 begin
2509 -- Check for unanalyzed aspects in the body that will
2510 -- generate a contract.
2512 if Present (Aspect_Specifications (N)) then
2513 A_Spec := First (Aspect_Specifications (N));
2514 while Present (A_Spec) loop
2515 A := Get_Aspect_Id (Chars (Identifier (A_Spec)));
2517 if A = Aspect_Contract_Cases or else
2518 A = Aspect_Depends or else
2519 A = Aspect_Global or else
2520 A = Aspect_Pre or else
2521 A = Aspect_Precondition or else
2522 A = Aspect_Post or else
2523 A = Aspect_Postcondition
2524 then
2525 return True;
2526 end if;
2528 Next (A_Spec);
2529 end loop;
2530 end if;
2532 -- Check for pragmas that may generate a contract
2534 if Present (Decls) then
2535 Decl := First (Decls);
2536 while Present (Decl) loop
2537 if Nkind (Decl) = N_Pragma then
2538 P_Id := Get_Pragma_Id (Pragma_Name (Decl));
2540 if P_Id = Pragma_Contract_Cases or else
2541 P_Id = Pragma_Depends or else
2542 P_Id = Pragma_Global or else
2543 P_Id = Pragma_Pre or else
2544 P_Id = Pragma_Precondition or else
2545 P_Id = Pragma_Post or else
2546 P_Id = Pragma_Postcondition
2547 then
2548 return True;
2549 end if;
2550 end if;
2552 Next (Decl);
2553 end loop;
2554 end if;
2556 return False;
2557 end Body_Has_Contract;
2559 ----------------------------
2560 -- Check_Anonymous_Return --
2561 ----------------------------
2563 procedure Check_Anonymous_Return is
2564 Decl : Node_Id;
2565 Par : Node_Id;
2566 Scop : Entity_Id;
2568 begin
2569 if Present (Spec_Id) then
2570 Scop := Spec_Id;
2571 else
2572 Scop := Body_Id;
2573 end if;
2575 if Ekind (Scop) = E_Function
2576 and then Ekind (Etype (Scop)) = E_Anonymous_Access_Type
2577 and then not Is_Thunk (Scop)
2579 -- Skip internally built functions which handle the case of
2580 -- a null access (see Expand_Interface_Conversion)
2582 and then not (Is_Interface (Designated_Type (Etype (Scop)))
2583 and then not Comes_From_Source (Parent (Scop)))
2585 and then (Has_Task (Designated_Type (Etype (Scop)))
2586 or else
2587 (Is_Class_Wide_Type (Designated_Type (Etype (Scop)))
2588 and then
2589 Is_Limited_Record (Designated_Type (Etype (Scop)))))
2590 and then Expander_Active
2592 -- Avoid cases with no tasking support
2594 and then RTE_Available (RE_Current_Master)
2595 and then not Restriction_Active (No_Task_Hierarchy)
2596 then
2597 Decl :=
2598 Make_Object_Declaration (Loc,
2599 Defining_Identifier =>
2600 Make_Defining_Identifier (Loc, Name_uMaster),
2601 Constant_Present => True,
2602 Object_Definition =>
2603 New_Occurrence_Of (RTE (RE_Master_Id), Loc),
2604 Expression =>
2605 Make_Explicit_Dereference (Loc,
2606 New_Occurrence_Of (RTE (RE_Current_Master), Loc)));
2608 if Present (Declarations (N)) then
2609 Prepend (Decl, Declarations (N));
2610 else
2611 Set_Declarations (N, New_List (Decl));
2612 end if;
2614 Set_Master_Id (Etype (Scop), Defining_Identifier (Decl));
2615 Set_Has_Master_Entity (Scop);
2617 -- Now mark the containing scope as a task master
2619 Par := N;
2620 while Nkind (Par) /= N_Compilation_Unit loop
2621 Par := Parent (Par);
2622 pragma Assert (Present (Par));
2624 -- If we fall off the top, we are at the outer level, and
2625 -- the environment task is our effective master, so nothing
2626 -- to mark.
2628 if Nkind_In
2629 (Par, N_Task_Body, N_Block_Statement, N_Subprogram_Body)
2630 then
2631 Set_Is_Task_Master (Par, True);
2632 exit;
2633 end if;
2634 end loop;
2635 end if;
2636 end Check_Anonymous_Return;
2638 -------------------------
2639 -- Check_Inline_Pragma --
2640 -------------------------
2642 procedure Check_Inline_Pragma (Spec : in out Node_Id) is
2643 Prag : Node_Id;
2644 Plist : List_Id;
2646 function Is_Inline_Pragma (N : Node_Id) return Boolean;
2647 -- True when N is a pragma Inline or Inline_Always that applies
2648 -- to this subprogram.
2650 -----------------------
2651 -- Is_Inline_Pragma --
2652 -----------------------
2654 function Is_Inline_Pragma (N : Node_Id) return Boolean is
2655 begin
2656 return
2657 Nkind (N) = N_Pragma
2658 and then
2659 (Pragma_Name (N) = Name_Inline_Always
2660 or else (Front_End_Inlining
2661 and then Pragma_Name (N) = Name_Inline))
2662 and then
2663 Chars
2664 (Expression (First (Pragma_Argument_Associations (N)))) =
2665 Chars (Body_Id);
2666 end Is_Inline_Pragma;
2668 -- Start of processing for Check_Inline_Pragma
2670 begin
2671 if not Expander_Active then
2672 return;
2673 end if;
2675 if Is_List_Member (N)
2676 and then Present (Next (N))
2677 and then Is_Inline_Pragma (Next (N))
2678 then
2679 Prag := Next (N);
2681 elsif Nkind (N) /= N_Subprogram_Body_Stub
2682 and then Present (Declarations (N))
2683 and then Is_Inline_Pragma (First (Declarations (N)))
2684 then
2685 Prag := First (Declarations (N));
2687 else
2688 Prag := Empty;
2689 end if;
2691 if Present (Prag) then
2692 if Present (Spec_Id) then
2693 if In_Same_List (N, Unit_Declaration_Node (Spec_Id)) then
2694 Analyze (Prag);
2695 end if;
2697 else
2698 -- Create a subprogram declaration, to make treatment uniform
2700 declare
2701 Subp : constant Entity_Id :=
2702 Make_Defining_Identifier (Loc, Chars (Body_Id));
2703 Decl : constant Node_Id :=
2704 Make_Subprogram_Declaration (Loc,
2705 Specification =>
2706 New_Copy_Tree (Specification (N)));
2708 begin
2709 Set_Defining_Unit_Name (Specification (Decl), Subp);
2711 if Present (First_Formal (Body_Id)) then
2712 Plist := Copy_Parameter_List (Body_Id);
2713 Set_Parameter_Specifications
2714 (Specification (Decl), Plist);
2715 end if;
2717 Insert_Before (N, Decl);
2718 Analyze (Decl);
2719 Analyze (Prag);
2720 Set_Has_Pragma_Inline (Subp);
2722 if Pragma_Name (Prag) = Name_Inline_Always then
2723 Set_Is_Inlined (Subp);
2724 Set_Has_Pragma_Inline_Always (Subp);
2725 end if;
2727 -- Prior to copying the subprogram body to create a template
2728 -- for it for subsequent inlining, remove the pragma from
2729 -- the current body so that the copy that will produce the
2730 -- new body will start from a completely unanalyzed tree.
2732 if Nkind (Parent (Prag)) = N_Subprogram_Body then
2733 Rewrite (Prag, Make_Null_Statement (Sloc (Prag)));
2734 end if;
2736 Spec := Subp;
2737 end;
2738 end if;
2739 end if;
2740 end Check_Inline_Pragma;
2742 --------------------------
2743 -- Check_Missing_Return --
2744 --------------------------
2746 procedure Check_Missing_Return is
2747 Id : Entity_Id;
2748 Missing_Ret : Boolean;
2750 begin
2751 if Nkind (Body_Spec) = N_Function_Specification then
2752 if Present (Spec_Id) then
2753 Id := Spec_Id;
2754 else
2755 Id := Body_Id;
2756 end if;
2758 if Return_Present (Id) then
2759 Check_Returns (HSS, 'F', Missing_Ret);
2761 if Missing_Ret then
2762 Set_Has_Missing_Return (Id);
2763 end if;
2765 elsif Is_Generic_Subprogram (Id)
2766 or else not Is_Machine_Code_Subprogram (Id)
2767 then
2768 Error_Msg_N ("missing RETURN statement in function body", N);
2769 end if;
2771 -- If procedure with No_Return, check returns
2773 elsif Nkind (Body_Spec) = N_Procedure_Specification
2774 and then Present (Spec_Id)
2775 and then No_Return (Spec_Id)
2776 then
2777 Check_Returns (HSS, 'P', Missing_Ret, Spec_Id);
2778 end if;
2780 -- Special checks in SPARK mode
2782 if Nkind (Body_Spec) = N_Function_Specification then
2784 -- In SPARK mode, last statement of a function should be a return
2786 declare
2787 Stat : constant Node_Id := Last_Source_Statement (HSS);
2788 begin
2789 if Present (Stat)
2790 and then not Nkind_In (Stat, N_Simple_Return_Statement,
2791 N_Extended_Return_Statement)
2792 then
2793 Check_SPARK_05_Restriction
2794 ("last statement in function should be RETURN", Stat);
2795 end if;
2796 end;
2798 -- In SPARK mode, verify that a procedure has no return
2800 elsif Nkind (Body_Spec) = N_Procedure_Specification then
2801 if Present (Spec_Id) then
2802 Id := Spec_Id;
2803 else
2804 Id := Body_Id;
2805 end if;
2807 -- Would be nice to point to return statement here, can we
2808 -- borrow the Check_Returns procedure here ???
2810 if Return_Present (Id) then
2811 Check_SPARK_05_Restriction
2812 ("procedure should not have RETURN", N);
2813 end if;
2814 end if;
2815 end Check_Missing_Return;
2817 -----------------------
2818 -- Disambiguate_Spec --
2819 -----------------------
2821 function Disambiguate_Spec return Entity_Id is
2822 Priv_Spec : Entity_Id;
2823 Spec_N : Entity_Id;
2825 procedure Replace_Types (To_Corresponding : Boolean);
2826 -- Depending on the flag, replace the type of formal parameters of
2827 -- Body_Id if it is a concurrent type implementing interfaces with
2828 -- the corresponding record type or the other way around.
2830 procedure Replace_Types (To_Corresponding : Boolean) is
2831 Formal : Entity_Id;
2832 Formal_Typ : Entity_Id;
2834 begin
2835 Formal := First_Formal (Body_Id);
2836 while Present (Formal) loop
2837 Formal_Typ := Etype (Formal);
2839 if Is_Class_Wide_Type (Formal_Typ) then
2840 Formal_Typ := Root_Type (Formal_Typ);
2841 end if;
2843 -- From concurrent type to corresponding record
2845 if To_Corresponding then
2846 if Is_Concurrent_Type (Formal_Typ)
2847 and then Present (Corresponding_Record_Type (Formal_Typ))
2848 and then
2849 Present (Interfaces
2850 (Corresponding_Record_Type (Formal_Typ)))
2851 then
2852 Set_Etype (Formal,
2853 Corresponding_Record_Type (Formal_Typ));
2854 end if;
2856 -- From corresponding record to concurrent type
2858 else
2859 if Is_Concurrent_Record_Type (Formal_Typ)
2860 and then Present (Interfaces (Formal_Typ))
2861 then
2862 Set_Etype (Formal,
2863 Corresponding_Concurrent_Type (Formal_Typ));
2864 end if;
2865 end if;
2867 Next_Formal (Formal);
2868 end loop;
2869 end Replace_Types;
2871 -- Start of processing for Disambiguate_Spec
2873 begin
2874 -- Try to retrieve the specification of the body as is. All error
2875 -- messages are suppressed because the body may not have a spec in
2876 -- its current state.
2878 Spec_N := Find_Corresponding_Spec (N, False);
2880 -- It is possible that this is the body of a primitive declared
2881 -- between a private and a full view of a concurrent type. The
2882 -- controlling parameter of the spec carries the concurrent type,
2883 -- not the corresponding record type as transformed by Analyze_
2884 -- Subprogram_Specification. In such cases, we undo the change
2885 -- made by the analysis of the specification and try to find the
2886 -- spec again.
2888 -- Note that wrappers already have their corresponding specs and
2889 -- bodies set during their creation, so if the candidate spec is
2890 -- a wrapper, then we definitely need to swap all types to their
2891 -- original concurrent status.
2893 if No (Spec_N)
2894 or else Is_Primitive_Wrapper (Spec_N)
2895 then
2896 -- Restore all references of corresponding record types to the
2897 -- original concurrent types.
2899 Replace_Types (To_Corresponding => False);
2900 Priv_Spec := Find_Corresponding_Spec (N, False);
2902 -- The current body truly belongs to a primitive declared between
2903 -- a private and a full view. We leave the modified body as is,
2904 -- and return the true spec.
2906 if Present (Priv_Spec)
2907 and then Is_Private_Primitive (Priv_Spec)
2908 then
2909 return Priv_Spec;
2910 end if;
2912 -- In case that this is some sort of error, restore the original
2913 -- state of the body.
2915 Replace_Types (To_Corresponding => True);
2916 end if;
2918 return Spec_N;
2919 end Disambiguate_Spec;
2921 ----------------------------
2922 -- Exchange_Limited_Views --
2923 ----------------------------
2925 procedure Exchange_Limited_Views (Subp_Id : Entity_Id) is
2926 procedure Detect_And_Exchange (Id : Entity_Id);
2927 -- Determine whether Id's type denotes an incomplete type associated
2928 -- with a limited with clause and exchange the limited view with the
2929 -- non-limited one.
2931 -------------------------
2932 -- Detect_And_Exchange --
2933 -------------------------
2935 procedure Detect_And_Exchange (Id : Entity_Id) is
2936 Typ : constant Entity_Id := Etype (Id);
2938 begin
2939 if Ekind (Typ) = E_Incomplete_Type
2940 and then From_Limited_With (Typ)
2941 and then Present (Non_Limited_View (Typ))
2942 then
2943 Set_Etype (Id, Non_Limited_View (Typ));
2944 end if;
2945 end Detect_And_Exchange;
2947 -- Local variables
2949 Formal : Entity_Id;
2951 -- Start of processing for Exchange_Limited_Views
2953 begin
2954 if No (Subp_Id) then
2955 return;
2957 -- Do not process subprogram bodies as they already use the non-
2958 -- limited view of types.
2960 elsif not Ekind_In (Subp_Id, E_Function, E_Procedure) then
2961 return;
2962 end if;
2964 -- Examine all formals and swap views when applicable
2966 Formal := First_Formal (Subp_Id);
2967 while Present (Formal) loop
2968 Detect_And_Exchange (Formal);
2970 Next_Formal (Formal);
2971 end loop;
2973 -- Process the return type of a function
2975 if Ekind (Subp_Id) = E_Function then
2976 Detect_And_Exchange (Subp_Id);
2977 end if;
2978 end Exchange_Limited_Views;
2980 -------------------------------------
2981 -- Is_Private_Concurrent_Primitive --
2982 -------------------------------------
2984 function Is_Private_Concurrent_Primitive
2985 (Subp_Id : Entity_Id) return Boolean
2987 Formal_Typ : Entity_Id;
2989 begin
2990 if Present (First_Formal (Subp_Id)) then
2991 Formal_Typ := Etype (First_Formal (Subp_Id));
2993 if Is_Concurrent_Record_Type (Formal_Typ) then
2994 if Is_Class_Wide_Type (Formal_Typ) then
2995 Formal_Typ := Root_Type (Formal_Typ);
2996 end if;
2998 Formal_Typ := Corresponding_Concurrent_Type (Formal_Typ);
2999 end if;
3001 -- The type of the first formal is a concurrent tagged type with
3002 -- a private view.
3004 return
3005 Is_Concurrent_Type (Formal_Typ)
3006 and then Is_Tagged_Type (Formal_Typ)
3007 and then Has_Private_Declaration (Formal_Typ);
3008 end if;
3010 return False;
3011 end Is_Private_Concurrent_Primitive;
3013 ----------------------------
3014 -- Set_Trivial_Subprogram --
3015 ----------------------------
3017 procedure Set_Trivial_Subprogram (N : Node_Id) is
3018 Nxt : constant Node_Id := Next (N);
3020 begin
3021 Set_Is_Trivial_Subprogram (Body_Id);
3023 if Present (Spec_Id) then
3024 Set_Is_Trivial_Subprogram (Spec_Id);
3025 end if;
3027 if Present (Nxt)
3028 and then Nkind (Nxt) = N_Simple_Return_Statement
3029 and then No (Next (Nxt))
3030 and then Present (Expression (Nxt))
3031 and then Is_Entity_Name (Expression (Nxt))
3032 then
3033 Set_Never_Set_In_Source (Entity (Expression (Nxt)), False);
3034 end if;
3035 end Set_Trivial_Subprogram;
3037 ---------------------------------
3038 -- Verify_Overriding_Indicator --
3039 ---------------------------------
3041 procedure Verify_Overriding_Indicator is
3042 begin
3043 if Must_Override (Body_Spec) then
3044 if Nkind (Spec_Id) = N_Defining_Operator_Symbol
3045 and then Operator_Matches_Spec (Spec_Id, Spec_Id)
3046 then
3047 null;
3049 elsif not Present (Overridden_Operation (Spec_Id)) then
3050 Error_Msg_NE
3051 ("subprogram& is not overriding", Body_Spec, Spec_Id);
3053 -- Overriding indicators aren't allowed for protected subprogram
3054 -- bodies (see the Confirmation in Ada Comment AC95-00213). Change
3055 -- this to a warning if -gnatd.E is enabled.
3057 elsif Ekind (Scope (Spec_Id)) = E_Protected_Type then
3058 Error_Msg_Warn := Error_To_Warning;
3059 Error_Msg_N
3060 ("<<overriding indicator not allowed for protected "
3061 & "subprogram body", Body_Spec);
3062 end if;
3064 elsif Must_Not_Override (Body_Spec) then
3065 if Present (Overridden_Operation (Spec_Id)) then
3066 Error_Msg_NE
3067 ("subprogram& overrides inherited operation",
3068 Body_Spec, Spec_Id);
3070 elsif Nkind (Spec_Id) = N_Defining_Operator_Symbol
3071 and then Operator_Matches_Spec (Spec_Id, Spec_Id)
3072 then
3073 Error_Msg_NE
3074 ("subprogram& overrides predefined operator ",
3075 Body_Spec, Spec_Id);
3077 -- Overriding indicators aren't allowed for protected subprogram
3078 -- bodies (see the Confirmation in Ada Comment AC95-00213). Change
3079 -- this to a warning if -gnatd.E is enabled.
3081 elsif Ekind (Scope (Spec_Id)) = E_Protected_Type then
3082 Error_Msg_Warn := Error_To_Warning;
3084 Error_Msg_N
3085 ("<<overriding indicator not allowed "
3086 & "for protected subprogram body", Body_Spec);
3088 -- If this is not a primitive operation, then the overriding
3089 -- indicator is altogether illegal.
3091 elsif not Is_Primitive (Spec_Id) then
3092 Error_Msg_N
3093 ("overriding indicator only allowed "
3094 & "if subprogram is primitive", Body_Spec);
3095 end if;
3097 -- If checking the style rule and the operation overrides, then
3098 -- issue a warning about a missing overriding_indicator. Protected
3099 -- subprogram bodies are excluded from this style checking, since
3100 -- they aren't primitives (even though their declarations can
3101 -- override) and aren't allowed to have an overriding_indicator.
3103 elsif Style_Check
3104 and then Present (Overridden_Operation (Spec_Id))
3105 and then Ekind (Scope (Spec_Id)) /= E_Protected_Type
3106 then
3107 pragma Assert (Unit_Declaration_Node (Body_Id) = N);
3108 Style.Missing_Overriding (N, Body_Id);
3110 elsif Style_Check
3111 and then Can_Override_Operator (Spec_Id)
3112 and then not Is_Predefined_File_Name
3113 (Unit_File_Name (Get_Source_Unit (Spec_Id)))
3114 then
3115 pragma Assert (Unit_Declaration_Node (Body_Id) = N);
3116 Style.Missing_Overriding (N, Body_Id);
3117 end if;
3118 end Verify_Overriding_Indicator;
3120 -- Start of processing for Analyze_Subprogram_Body_Helper
3122 begin
3123 -- Generic subprograms are handled separately. They always have a
3124 -- generic specification. Determine whether current scope has a
3125 -- previous declaration.
3127 -- If the subprogram body is defined within an instance of the same
3128 -- name, the instance appears as a package renaming, and will be hidden
3129 -- within the subprogram.
3131 if Present (Prev_Id)
3132 and then not Is_Overloadable (Prev_Id)
3133 and then (Nkind (Parent (Prev_Id)) /= N_Package_Renaming_Declaration
3134 or else Comes_From_Source (Prev_Id))
3135 then
3136 if Is_Generic_Subprogram (Prev_Id) then
3137 Spec_Id := Prev_Id;
3139 -- The corresponding spec may be subject to pragma Ghost with
3140 -- policy Ignore. Set the mode now to ensure that any nodes
3141 -- generated during analysis and expansion are properly flagged
3142 -- as ignored Ghost.
3144 Set_Ghost_Mode (N, Spec_Id);
3145 Set_Is_Compilation_Unit (Body_Id, Is_Compilation_Unit (Spec_Id));
3146 Set_Is_Child_Unit (Body_Id, Is_Child_Unit (Spec_Id));
3148 Analyze_Generic_Subprogram_Body (N, Spec_Id);
3150 if Nkind (N) = N_Subprogram_Body then
3151 HSS := Handled_Statement_Sequence (N);
3152 Check_Missing_Return;
3153 end if;
3155 return;
3157 else
3158 -- Previous entity conflicts with subprogram name. Attempting to
3159 -- enter name will post error.
3161 Enter_Name (Body_Id);
3162 return;
3163 end if;
3165 -- Non-generic case, find the subprogram declaration, if one was seen,
3166 -- or enter new overloaded entity in the current scope. If the
3167 -- Current_Entity is the Body_Id itself, the unit is being analyzed as
3168 -- part of the context of one of its subunits. No need to redo the
3169 -- analysis.
3171 elsif Prev_Id = Body_Id and then Has_Completion (Body_Id) then
3172 return;
3174 else
3175 Body_Id := Analyze_Subprogram_Specification (Body_Spec);
3177 if Nkind (N) = N_Subprogram_Body_Stub
3178 or else No (Corresponding_Spec (N))
3179 then
3180 if Is_Private_Concurrent_Primitive (Body_Id) then
3181 Spec_Id := Disambiguate_Spec;
3183 -- The corresponding spec may be subject to pragma Ghost with
3184 -- policy Ignore. Set the mode now to ensure that any nodes
3185 -- generated during analysis and expansion are properly flagged
3186 -- as ignored Ghost.
3188 Set_Ghost_Mode (N, Spec_Id);
3190 else
3191 Spec_Id := Find_Corresponding_Spec (N);
3193 -- The corresponding spec may be subject to pragma Ghost with
3194 -- policy Ignore. Set the mode now to ensure that any nodes
3195 -- generated during analysis and expansion are properly flagged
3196 -- as ignored Ghost.
3198 Set_Ghost_Mode (N, Spec_Id);
3200 -- In GNATprove mode, if the body has no previous spec, create
3201 -- one so that the inlining machinery can operate properly.
3202 -- Transfer aspects, if any, to the new spec, so that they
3203 -- are legal and can be processed ahead of the body.
3204 -- We make two copies of the given spec, one for the new
3205 -- declaration, and one for the body.
3207 if No (Spec_Id)
3208 and then GNATprove_Mode
3210 -- Inlining does not apply during pre-analysis of code
3212 and then Full_Analysis
3214 -- Inlining only applies to full bodies, not stubs
3216 and then Nkind (N) /= N_Subprogram_Body_Stub
3218 -- Inlining only applies to bodies in the source code, not to
3219 -- those generated by the compiler. In particular, expression
3220 -- functions, whose body is generated by the compiler, are
3221 -- treated specially by GNATprove.
3223 and then Comes_From_Source (Body_Id)
3225 -- This cannot be done for a compilation unit, which is not
3226 -- in a context where we can insert a new spec.
3228 and then Is_List_Member (N)
3230 -- Inlining only applies to subprograms without contracts,
3231 -- as a contract is a sign that GNATprove should perform a
3232 -- modular analysis of the subprogram instead of a contextual
3233 -- analysis at each call site. The same test is performed in
3234 -- Inline.Can_Be_Inlined_In_GNATprove_Mode. It is repeated
3235 -- here in another form (because the contract has not
3236 -- been attached to the body) to avoid frontend errors in
3237 -- case pragmas are used instead of aspects, because the
3238 -- corresponding pragmas in the body would not be transferred
3239 -- to the spec, leading to legality errors.
3241 and then not Body_Has_Contract
3242 then
3243 declare
3244 Body_Spec : constant Node_Id :=
3245 Copy_Separate_Tree (Specification (N));
3246 New_Decl : constant Node_Id :=
3247 Make_Subprogram_Declaration (Loc,
3248 Copy_Separate_Tree (Specification (N)));
3250 SPARK_Mode_Aspect : Node_Id;
3251 Aspects : List_Id;
3252 Prag, Aspect : Node_Id;
3254 begin
3255 Insert_Before (N, New_Decl);
3256 Move_Aspects (From => N, To => New_Decl);
3258 -- Mark the newly moved aspects as not analyzed, so that
3259 -- their effect on New_Decl is properly analyzed.
3261 Aspect := First (Aspect_Specifications (New_Decl));
3262 while Present (Aspect) loop
3263 Set_Analyzed (Aspect, False);
3264 Next (Aspect);
3265 end loop;
3267 Analyze (New_Decl);
3269 -- The analysis of the generated subprogram declaration
3270 -- may have introduced pragmas that need to be analyzed.
3272 Prag := Next (New_Decl);
3273 while Prag /= N loop
3274 Analyze (Prag);
3275 Next (Prag);
3276 end loop;
3278 Spec_Id := Defining_Entity (New_Decl);
3280 -- As Body_Id originally comes from source, mark the new
3281 -- Spec_Id as such, which is required so that calls to
3282 -- this subprogram are registered in the local effects
3283 -- stored in ALI files for GNATprove.
3285 Set_Comes_From_Source (Spec_Id, True);
3287 -- If aspect SPARK_Mode was specified on the body, it
3288 -- needs to be repeated on the generated decl and the
3289 -- body. Since the original aspect was moved to the
3290 -- generated decl, copy it for the body.
3292 if Has_Aspect (Spec_Id, Aspect_SPARK_Mode) then
3293 SPARK_Mode_Aspect :=
3294 New_Copy (Find_Aspect (Spec_Id, Aspect_SPARK_Mode));
3295 Set_Analyzed (SPARK_Mode_Aspect, False);
3296 Aspects := New_List (SPARK_Mode_Aspect);
3297 Set_Aspect_Specifications (N, Aspects);
3298 end if;
3300 Set_Specification (N, Body_Spec);
3301 Body_Id := Analyze_Subprogram_Specification (Body_Spec);
3302 Set_Corresponding_Spec (N, Spec_Id);
3303 end;
3304 end if;
3305 end if;
3307 -- If this is a duplicate body, no point in analyzing it
3309 if Error_Posted (N) then
3310 return;
3311 end if;
3313 -- A subprogram body should cause freezing of its own declaration,
3314 -- but if there was no previous explicit declaration, then the
3315 -- subprogram will get frozen too late (there may be code within
3316 -- the body that depends on the subprogram having been frozen,
3317 -- such as uses of extra formals), so we force it to be frozen
3318 -- here. Same holds if the body and spec are compilation units.
3319 -- Finally, if the return type is an anonymous access to protected
3320 -- subprogram, it must be frozen before the body because its
3321 -- expansion has generated an equivalent type that is used when
3322 -- elaborating the body.
3324 -- An exception in the case of Ada 2012, AI05-177: The bodies
3325 -- created for expression functions do not freeze.
3327 if No (Spec_Id)
3328 and then Nkind (Original_Node (N)) /= N_Expression_Function
3329 then
3330 Freeze_Before (N, Body_Id);
3332 elsif Nkind (Parent (N)) = N_Compilation_Unit then
3333 Freeze_Before (N, Spec_Id);
3335 elsif Is_Access_Subprogram_Type (Etype (Body_Id)) then
3336 Freeze_Before (N, Etype (Body_Id));
3337 end if;
3339 else
3340 Spec_Id := Corresponding_Spec (N);
3342 -- The corresponding spec may be subject to pragma Ghost with
3343 -- policy Ignore. Set the mode now to ensure that any nodes
3344 -- generated during analysis and expansion are properly flagged
3345 -- as ignored Ghost.
3347 Set_Ghost_Mode (N, Spec_Id);
3348 end if;
3349 end if;
3351 -- Previously we scanned the body to look for nested subprograms, and
3352 -- rejected an inline directive if nested subprograms were present,
3353 -- because the back-end would generate conflicting symbols for the
3354 -- nested bodies. This is now unnecessary.
3356 -- Look ahead to recognize a pragma Inline that appears after the body
3358 Check_Inline_Pragma (Spec_Id);
3360 -- Deal with special case of a fully private operation in the body of
3361 -- the protected type. We must create a declaration for the subprogram,
3362 -- in order to attach the protected subprogram that will be used in
3363 -- internal calls. We exclude compiler generated bodies from the
3364 -- expander since the issue does not arise for those cases.
3366 if No (Spec_Id)
3367 and then Comes_From_Source (N)
3368 and then Is_Protected_Type (Current_Scope)
3369 then
3370 Spec_Id := Build_Private_Protected_Declaration (N);
3371 end if;
3373 -- If a separate spec is present, then deal with freezing issues
3375 if Present (Spec_Id) then
3376 Spec_Decl := Unit_Declaration_Node (Spec_Id);
3377 Verify_Overriding_Indicator;
3379 -- In general, the spec will be frozen when we start analyzing the
3380 -- body. However, for internally generated operations, such as
3381 -- wrapper functions for inherited operations with controlling
3382 -- results, the spec may not have been frozen by the time we expand
3383 -- the freeze actions that include the bodies. In particular, extra
3384 -- formals for accessibility or for return-in-place may need to be
3385 -- generated. Freeze nodes, if any, are inserted before the current
3386 -- body. These freeze actions are also needed in ASIS mode to enable
3387 -- the proper back-annotations.
3389 if not Is_Frozen (Spec_Id)
3390 and then (Expander_Active or ASIS_Mode)
3391 then
3392 -- Force the generation of its freezing node to ensure proper
3393 -- management of access types in the backend.
3395 -- This is definitely needed for some cases, but it is not clear
3396 -- why, to be investigated further???
3398 Set_Has_Delayed_Freeze (Spec_Id);
3399 Freeze_Before (N, Spec_Id);
3400 end if;
3401 end if;
3403 -- Mark presence of postcondition procedure in current scope and mark
3404 -- the procedure itself as needing debug info. The latter is important
3405 -- when analyzing decision coverage (for example, for MC/DC coverage).
3407 if Chars (Body_Id) = Name_uPostconditions then
3408 Set_Has_Postconditions (Current_Scope);
3409 Set_Debug_Info_Needed (Body_Id);
3410 end if;
3412 -- Place subprogram on scope stack, and make formals visible. If there
3413 -- is a spec, the visible entity remains that of the spec.
3415 if Present (Spec_Id) then
3416 Generate_Reference (Spec_Id, Body_Id, 'b', Set_Ref => False);
3418 if Is_Child_Unit (Spec_Id) then
3419 Generate_Reference (Spec_Id, Scope (Spec_Id), 'k', False);
3420 end if;
3422 if Style_Check then
3423 Style.Check_Identifier (Body_Id, Spec_Id);
3424 end if;
3426 Set_Is_Compilation_Unit (Body_Id, Is_Compilation_Unit (Spec_Id));
3427 Set_Is_Child_Unit (Body_Id, Is_Child_Unit (Spec_Id));
3429 if Is_Abstract_Subprogram (Spec_Id) then
3430 Error_Msg_N ("an abstract subprogram cannot have a body", N);
3431 return;
3433 else
3434 Set_Convention (Body_Id, Convention (Spec_Id));
3435 Set_Has_Completion (Spec_Id);
3437 -- Inherit the "ghostness" of the subprogram spec. Note that this
3438 -- property is not directly inherited as the body may be subject
3439 -- to a different Ghost assertion policy.
3441 if Is_Ghost_Entity (Spec_Id) or else Ghost_Mode > None then
3442 Set_Is_Ghost_Entity (Body_Id);
3444 -- The Ghost policy in effect at the point of declaration and
3445 -- at the point of completion must match (SPARK RM 6.9(15)).
3447 Check_Ghost_Completion (Spec_Id, Body_Id);
3448 end if;
3450 if Is_Protected_Type (Scope (Spec_Id)) then
3451 Prot_Typ := Scope (Spec_Id);
3452 end if;
3454 -- If this is a body generated for a renaming, do not check for
3455 -- full conformance. The check is redundant, because the spec of
3456 -- the body is a copy of the spec in the renaming declaration,
3457 -- and the test can lead to spurious errors on nested defaults.
3459 if Present (Spec_Decl)
3460 and then not Comes_From_Source (N)
3461 and then
3462 (Nkind (Original_Node (Spec_Decl)) =
3463 N_Subprogram_Renaming_Declaration
3464 or else (Present (Corresponding_Body (Spec_Decl))
3465 and then
3466 Nkind (Unit_Declaration_Node
3467 (Corresponding_Body (Spec_Decl))) =
3468 N_Subprogram_Renaming_Declaration))
3469 then
3470 Conformant := True;
3472 -- Conversely, the spec may have been generated for specless body
3473 -- with an inline pragma.
3475 elsif Comes_From_Source (N)
3476 and then not Comes_From_Source (Spec_Id)
3477 and then Has_Pragma_Inline (Spec_Id)
3478 then
3479 Conformant := True;
3481 else
3482 Check_Conformance
3483 (Body_Id, Spec_Id,
3484 Fully_Conformant, True, Conformant, Body_Id);
3485 end if;
3487 -- If the body is not fully conformant, we have to decide if we
3488 -- should analyze it or not. If it has a really messed up profile
3489 -- then we probably should not analyze it, since we will get too
3490 -- many bogus messages.
3492 -- Our decision is to go ahead in the non-fully conformant case
3493 -- only if it is at least mode conformant with the spec. Note
3494 -- that the call to Check_Fully_Conformant has issued the proper
3495 -- error messages to complain about the lack of conformance.
3497 if not Conformant
3498 and then not Mode_Conformant (Body_Id, Spec_Id)
3499 then
3500 return;
3501 end if;
3502 end if;
3504 if Spec_Id /= Body_Id then
3505 Reference_Body_Formals (Spec_Id, Body_Id);
3506 end if;
3508 Set_Ekind (Body_Id, E_Subprogram_Body);
3510 if Nkind (N) = N_Subprogram_Body_Stub then
3511 Set_Corresponding_Spec_Of_Stub (N, Spec_Id);
3513 -- Regular body
3515 else
3516 Set_Corresponding_Spec (N, Spec_Id);
3518 -- Ada 2005 (AI-345): If the operation is a primitive operation
3519 -- of a concurrent type, the type of the first parameter has been
3520 -- replaced with the corresponding record, which is the proper
3521 -- run-time structure to use. However, within the body there may
3522 -- be uses of the formals that depend on primitive operations
3523 -- of the type (in particular calls in prefixed form) for which
3524 -- we need the original concurrent type. The operation may have
3525 -- several controlling formals, so the replacement must be done
3526 -- for all of them.
3528 if Comes_From_Source (Spec_Id)
3529 and then Present (First_Entity (Spec_Id))
3530 and then Ekind (Etype (First_Entity (Spec_Id))) = E_Record_Type
3531 and then Is_Tagged_Type (Etype (First_Entity (Spec_Id)))
3532 and then Present (Interfaces (Etype (First_Entity (Spec_Id))))
3533 and then Present (Corresponding_Concurrent_Type
3534 (Etype (First_Entity (Spec_Id))))
3535 then
3536 declare
3537 Typ : constant Entity_Id := Etype (First_Entity (Spec_Id));
3538 Form : Entity_Id;
3540 begin
3541 Form := First_Formal (Spec_Id);
3542 while Present (Form) loop
3543 if Etype (Form) = Typ then
3544 Set_Etype (Form, Corresponding_Concurrent_Type (Typ));
3545 end if;
3547 Next_Formal (Form);
3548 end loop;
3549 end;
3550 end if;
3552 -- Make the formals visible, and place subprogram on scope stack.
3553 -- This is also the point at which we set Last_Real_Spec_Entity
3554 -- to mark the entities which will not be moved to the body.
3556 Install_Formals (Spec_Id);
3557 Last_Real_Spec_Entity := Last_Entity (Spec_Id);
3559 -- Within an instance, add local renaming declarations so that
3560 -- gdb can retrieve the values of actuals more easily. This is
3561 -- only relevant if generating code (and indeed we definitely
3562 -- do not want these definitions -gnatc mode, because that would
3563 -- confuse ASIS).
3565 if Is_Generic_Instance (Spec_Id)
3566 and then Is_Wrapper_Package (Current_Scope)
3567 and then Expander_Active
3568 then
3569 Build_Subprogram_Instance_Renamings (N, Current_Scope);
3570 end if;
3572 Push_Scope (Spec_Id);
3574 -- Make sure that the subprogram is immediately visible. For
3575 -- child units that have no separate spec this is indispensable.
3576 -- Otherwise it is safe albeit redundant.
3578 Set_Is_Immediately_Visible (Spec_Id);
3579 end if;
3581 Set_Corresponding_Body (Unit_Declaration_Node (Spec_Id), Body_Id);
3582 Set_Contract (Body_Id, Make_Contract (Sloc (Body_Id)));
3583 Set_Scope (Body_Id, Scope (Spec_Id));
3584 Set_Is_Obsolescent (Body_Id, Is_Obsolescent (Spec_Id));
3586 -- Case of subprogram body with no previous spec
3588 else
3589 -- Check for style warning required
3591 if Style_Check
3593 -- Only apply check for source level subprograms for which checks
3594 -- have not been suppressed.
3596 and then Comes_From_Source (Body_Id)
3597 and then not Suppress_Style_Checks (Body_Id)
3599 -- No warnings within an instance
3601 and then not In_Instance
3603 -- No warnings for expression functions
3605 and then Nkind (Original_Node (N)) /= N_Expression_Function
3606 then
3607 Style.Body_With_No_Spec (N);
3608 end if;
3610 New_Overloaded_Entity (Body_Id);
3612 if Nkind (N) /= N_Subprogram_Body_Stub then
3613 Set_Acts_As_Spec (N);
3614 Generate_Definition (Body_Id);
3615 Set_Contract (Body_Id, Make_Contract (Sloc (Body_Id)));
3616 Generate_Reference
3617 (Body_Id, Body_Id, 'b', Set_Ref => False, Force => True);
3618 Install_Formals (Body_Id);
3620 Push_Scope (Body_Id);
3621 end if;
3623 -- For stubs and bodies with no previous spec, generate references to
3624 -- formals.
3626 Generate_Reference_To_Formals (Body_Id);
3627 end if;
3629 -- Set SPARK_Mode from context
3631 Set_SPARK_Pragma (Body_Id, SPARK_Mode_Pragma);
3632 Set_SPARK_Pragma_Inherited (Body_Id, True);
3634 -- If the return type is an anonymous access type whose designated type
3635 -- is the limited view of a class-wide type and the non-limited view is
3636 -- available, update the return type accordingly.
3638 if Ada_Version >= Ada_2005 and then Comes_From_Source (N) then
3639 declare
3640 Etyp : Entity_Id;
3641 Rtyp : Entity_Id;
3643 begin
3644 Rtyp := Etype (Current_Scope);
3646 if Ekind (Rtyp) = E_Anonymous_Access_Type then
3647 Etyp := Directly_Designated_Type (Rtyp);
3649 if Is_Class_Wide_Type (Etyp)
3650 and then From_Limited_With (Etyp)
3651 then
3652 Set_Directly_Designated_Type
3653 (Etype (Current_Scope), Available_View (Etyp));
3654 end if;
3655 end if;
3656 end;
3657 end if;
3659 -- If this is the proper body of a stub, we must verify that the stub
3660 -- conforms to the body, and to the previous spec if one was present.
3661 -- We know already that the body conforms to that spec. This test is
3662 -- only required for subprograms that come from source.
3664 if Nkind (Parent (N)) = N_Subunit
3665 and then Comes_From_Source (N)
3666 and then not Error_Posted (Body_Id)
3667 and then Nkind (Corresponding_Stub (Parent (N))) =
3668 N_Subprogram_Body_Stub
3669 then
3670 declare
3671 Old_Id : constant Entity_Id :=
3672 Defining_Entity
3673 (Specification (Corresponding_Stub (Parent (N))));
3675 Conformant : Boolean := False;
3677 begin
3678 if No (Spec_Id) then
3679 Check_Fully_Conformant (Body_Id, Old_Id);
3681 else
3682 Check_Conformance
3683 (Body_Id, Old_Id, Fully_Conformant, False, Conformant);
3685 if not Conformant then
3687 -- The stub was taken to be a new declaration. Indicate that
3688 -- it lacks a body.
3690 Set_Has_Completion (Old_Id, False);
3691 end if;
3692 end if;
3693 end;
3694 end if;
3696 Set_Has_Completion (Body_Id);
3697 Check_Eliminated (Body_Id);
3699 if Nkind (N) = N_Subprogram_Body_Stub then
3701 -- Analyze any aspect specifications that appear on the subprogram
3702 -- body stub.
3704 if Has_Aspects (N) then
3705 Analyze_Aspects_On_Body_Or_Stub;
3706 end if;
3708 -- Stop the analysis now as the stub cannot be inlined, plus it does
3709 -- not have declarative or statement lists.
3711 return;
3712 end if;
3714 -- Handle frontend inlining
3716 -- Note: Normally we don't do any inlining if expansion is off, since
3717 -- we won't generate code in any case. An exception arises in GNATprove
3718 -- mode where we want to expand some calls in place, even with expansion
3719 -- disabled, since the inlining eases formal verification.
3721 if not GNATprove_Mode
3722 and then Expander_Active
3723 and then Serious_Errors_Detected = 0
3724 and then Present (Spec_Id)
3725 and then Has_Pragma_Inline (Spec_Id)
3726 then
3727 -- Legacy implementation (relying on frontend inlining)
3729 if not Back_End_Inlining then
3730 if Has_Pragma_Inline_Always (Spec_Id)
3731 or else (Has_Pragma_Inline (Spec_Id) and Front_End_Inlining)
3732 then
3733 Build_Body_To_Inline (N, Spec_Id);
3734 end if;
3736 -- New implementation (relying on backend inlining)
3738 else
3739 if Has_Pragma_Inline_Always (Spec_Id)
3740 or else Optimization_Level > 0
3741 then
3742 -- Handle function returning an unconstrained type
3744 if Comes_From_Source (Body_Id)
3745 and then Ekind (Spec_Id) = E_Function
3746 and then Returns_Unconstrained_Type (Spec_Id)
3748 -- If function builds in place, i.e. returns a limited type,
3749 -- inlining cannot be done.
3751 and then not Is_Limited_Type (Etype (Spec_Id))
3752 then
3753 Check_And_Split_Unconstrained_Function (N, Spec_Id, Body_Id);
3755 else
3756 declare
3757 Subp_Body : constant Node_Id :=
3758 Unit_Declaration_Node (Body_Id);
3759 Subp_Decl : constant List_Id := Declarations (Subp_Body);
3761 begin
3762 -- Do not pass inlining to the backend if the subprogram
3763 -- has declarations or statements which cannot be inlined
3764 -- by the backend. This check is done here to emit an
3765 -- error instead of the generic warning message reported
3766 -- by the GCC backend (ie. "function might not be
3767 -- inlinable").
3769 if Present (Subp_Decl)
3770 and then Has_Excluded_Declaration (Spec_Id, Subp_Decl)
3771 then
3772 null;
3774 elsif Has_Excluded_Statement
3775 (Spec_Id,
3776 Statements
3777 (Handled_Statement_Sequence (Subp_Body)))
3778 then
3779 null;
3781 -- If the backend inlining is available then at this
3782 -- stage we only have to mark the subprogram as inlined.
3783 -- The expander will take care of registering it in the
3784 -- table of subprograms inlined by the backend a part of
3785 -- processing calls to it (cf. Expand_Call)
3787 else
3788 Set_Is_Inlined (Spec_Id);
3789 end if;
3790 end;
3791 end if;
3792 end if;
3793 end if;
3795 -- In GNATprove mode, inline only when there is a separate subprogram
3796 -- declaration for now, as inlining of subprogram bodies acting as
3797 -- declarations, or subprogram stubs, are not supported by frontend
3798 -- inlining. This inlining should occur after analysis of the body, so
3799 -- that it is known whether the value of SPARK_Mode applicable to the
3800 -- body, which can be defined by a pragma inside the body.
3802 elsif GNATprove_Mode
3803 and then Full_Analysis
3804 and then not Inside_A_Generic
3805 and then Present (Spec_Id)
3806 and then Nkind (Parent (Parent (Spec_Id))) = N_Subprogram_Declaration
3807 and then Can_Be_Inlined_In_GNATprove_Mode (Spec_Id, Body_Id)
3808 and then not Body_Has_Contract
3809 then
3810 Build_Body_To_Inline (N, Spec_Id);
3811 end if;
3813 -- Ada 2005 (AI-262): In library subprogram bodies, after the analysis
3814 -- of the specification we have to install the private withed units.
3815 -- This holds for child units as well.
3817 if Is_Compilation_Unit (Body_Id)
3818 or else Nkind (Parent (N)) = N_Compilation_Unit
3819 then
3820 Install_Private_With_Clauses (Body_Id);
3821 end if;
3823 Check_Anonymous_Return;
3825 -- Set the Protected_Formal field of each extra formal of the protected
3826 -- subprogram to reference the corresponding extra formal of the
3827 -- subprogram that implements it. For regular formals this occurs when
3828 -- the protected subprogram's declaration is expanded, but the extra
3829 -- formals don't get created until the subprogram is frozen. We need to
3830 -- do this before analyzing the protected subprogram's body so that any
3831 -- references to the original subprogram's extra formals will be changed
3832 -- refer to the implementing subprogram's formals (see Expand_Formal).
3834 if Present (Spec_Id)
3835 and then Is_Protected_Type (Scope (Spec_Id))
3836 and then Present (Protected_Body_Subprogram (Spec_Id))
3837 then
3838 declare
3839 Impl_Subp : constant Entity_Id :=
3840 Protected_Body_Subprogram (Spec_Id);
3841 Prot_Ext_Formal : Entity_Id := Extra_Formals (Spec_Id);
3842 Impl_Ext_Formal : Entity_Id := Extra_Formals (Impl_Subp);
3843 begin
3844 while Present (Prot_Ext_Formal) loop
3845 pragma Assert (Present (Impl_Ext_Formal));
3846 Set_Protected_Formal (Prot_Ext_Formal, Impl_Ext_Formal);
3847 Next_Formal_With_Extras (Prot_Ext_Formal);
3848 Next_Formal_With_Extras (Impl_Ext_Formal);
3849 end loop;
3850 end;
3851 end if;
3853 -- Now we can go on to analyze the body
3855 HSS := Handled_Statement_Sequence (N);
3856 Set_Actual_Subtypes (N, Current_Scope);
3858 -- Add a declaration for the Protection object, renaming declarations
3859 -- for discriminals and privals and finally a declaration for the entry
3860 -- family index (if applicable). This form of early expansion is done
3861 -- when the Expander is active because Install_Private_Data_Declarations
3862 -- references entities which were created during regular expansion. The
3863 -- subprogram entity must come from source, and not be an internally
3864 -- generated subprogram.
3866 if Expander_Active
3867 and then Present (Prot_Typ)
3868 and then Present (Spec_Id)
3869 and then Comes_From_Source (Spec_Id)
3870 and then not Is_Eliminated (Spec_Id)
3871 then
3872 Install_Private_Data_Declarations
3873 (Sloc (N), Spec_Id, Prot_Typ, N, Declarations (N));
3874 end if;
3876 -- Ada 2012 (AI05-0151): Incomplete types coming from a limited context
3877 -- may now appear in parameter and result profiles. Since the analysis
3878 -- of a subprogram body may use the parameter and result profile of the
3879 -- spec, swap any limited views with their non-limited counterpart.
3881 if Ada_Version >= Ada_2012 then
3882 Exchange_Limited_Views (Spec_Id);
3883 end if;
3885 -- Analyze any aspect specifications that appear on the subprogram body
3887 if Has_Aspects (N) then
3888 Analyze_Aspects_On_Body_Or_Stub;
3889 end if;
3891 -- Deal with [refined] preconditions, postconditions, Contract_Cases,
3892 -- invariants and predicates associated with the body and its spec.
3893 -- Note that this is not pure expansion as Expand_Subprogram_Contract
3894 -- prepares the contract assertions for generic subprograms or for ASIS.
3895 -- Do not generate contract checks in SPARK mode.
3897 if not GNATprove_Mode then
3898 Expand_Subprogram_Contract (N, Spec_Id, Body_Id);
3899 end if;
3901 -- Analyze the declarations (this call will analyze the precondition
3902 -- Check pragmas we prepended to the list, as well as the declaration
3903 -- of the _Postconditions procedure).
3905 Analyze_Declarations (Declarations (N));
3907 -- Verify that the SPARK_Mode of the body agrees with that of its spec
3909 if Present (Spec_Id) and then Present (SPARK_Pragma (Body_Id)) then
3910 if Present (SPARK_Pragma (Spec_Id)) then
3911 if Get_SPARK_Mode_From_Pragma (SPARK_Pragma (Spec_Id)) = Off
3912 and then
3913 Get_SPARK_Mode_From_Pragma (SPARK_Pragma (Body_Id)) = On
3914 then
3915 Error_Msg_Sloc := Sloc (SPARK_Pragma (Body_Id));
3916 Error_Msg_N ("incorrect application of SPARK_Mode#", N);
3917 Error_Msg_Sloc := Sloc (SPARK_Pragma (Spec_Id));
3918 Error_Msg_NE
3919 ("\value Off was set for SPARK_Mode on & #", N, Spec_Id);
3920 end if;
3922 elsif Nkind (Parent (Parent (Spec_Id))) = N_Subprogram_Body_Stub then
3923 null;
3925 else
3926 Error_Msg_Sloc := Sloc (SPARK_Pragma (Body_Id));
3927 Error_Msg_N ("incorrect application of SPARK_Mode #", N);
3928 Error_Msg_Sloc := Sloc (Spec_Id);
3929 Error_Msg_NE
3930 ("\no value was set for SPARK_Mode on & #", N, Spec_Id);
3931 end if;
3932 end if;
3934 -- If SPARK_Mode for body is not On, disable frontend inlining for this
3935 -- subprogram in GNATprove mode, as its body should not be analyzed.
3937 if SPARK_Mode /= On
3938 and then GNATprove_Mode
3939 and then Present (Spec_Id)
3940 and then Nkind (Parent (Parent (Spec_Id))) = N_Subprogram_Declaration
3941 then
3942 Set_Body_To_Inline (Parent (Parent (Spec_Id)), Empty);
3943 Set_Is_Inlined_Always (Spec_Id, False);
3944 end if;
3946 -- Check completion, and analyze the statements
3948 Check_Completion;
3949 Inspect_Deferred_Constant_Completion (Declarations (N));
3950 Analyze (HSS);
3952 -- Deal with end of scope processing for the body
3954 Process_End_Label (HSS, 't', Current_Scope);
3955 End_Scope;
3956 Check_Subprogram_Order (N);
3957 Set_Analyzed (Body_Id);
3959 -- If we have a separate spec, then the analysis of the declarations
3960 -- caused the entities in the body to be chained to the spec id, but
3961 -- we want them chained to the body id. Only the formal parameters
3962 -- end up chained to the spec id in this case.
3964 if Present (Spec_Id) then
3966 -- We must conform to the categorization of our spec
3968 Validate_Categorization_Dependency (N, Spec_Id);
3970 -- And if this is a child unit, the parent units must conform
3972 if Is_Child_Unit (Spec_Id) then
3973 Validate_Categorization_Dependency
3974 (Unit_Declaration_Node (Spec_Id), Spec_Id);
3975 end if;
3977 -- Here is where we move entities from the spec to the body
3979 -- Case where there are entities that stay with the spec
3981 if Present (Last_Real_Spec_Entity) then
3983 -- No body entities (happens when the only real spec entities come
3984 -- from precondition and postcondition pragmas).
3986 if No (Last_Entity (Body_Id)) then
3987 Set_First_Entity
3988 (Body_Id, Next_Entity (Last_Real_Spec_Entity));
3990 -- Body entities present (formals), so chain stuff past them
3992 else
3993 Set_Next_Entity
3994 (Last_Entity (Body_Id), Next_Entity (Last_Real_Spec_Entity));
3995 end if;
3997 Set_Next_Entity (Last_Real_Spec_Entity, Empty);
3998 Set_Last_Entity (Body_Id, Last_Entity (Spec_Id));
3999 Set_Last_Entity (Spec_Id, Last_Real_Spec_Entity);
4001 -- Case where there are no spec entities, in this case there can be
4002 -- no body entities either, so just move everything.
4004 -- If the body is generated for an expression function, it may have
4005 -- been preanalyzed already, if 'access was applied to it.
4007 else
4008 if Nkind (Original_Node (Unit_Declaration_Node (Spec_Id))) /=
4009 N_Expression_Function
4010 then
4011 pragma Assert (No (Last_Entity (Body_Id)));
4012 null;
4013 end if;
4015 Set_First_Entity (Body_Id, First_Entity (Spec_Id));
4016 Set_Last_Entity (Body_Id, Last_Entity (Spec_Id));
4017 Set_First_Entity (Spec_Id, Empty);
4018 Set_Last_Entity (Spec_Id, Empty);
4019 end if;
4020 end if;
4022 Check_Missing_Return;
4024 -- Now we are going to check for variables that are never modified in
4025 -- the body of the procedure. But first we deal with a special case
4026 -- where we want to modify this check. If the body of the subprogram
4027 -- starts with a raise statement or its equivalent, or if the body
4028 -- consists entirely of a null statement, then it is pretty obvious that
4029 -- it is OK to not reference the parameters. For example, this might be
4030 -- the following common idiom for a stubbed function: statement of the
4031 -- procedure raises an exception. In particular this deals with the
4032 -- common idiom of a stubbed function, which appears something like:
4034 -- function F (A : Integer) return Some_Type;
4035 -- X : Some_Type;
4036 -- begin
4037 -- raise Program_Error;
4038 -- return X;
4039 -- end F;
4041 -- Here the purpose of X is simply to satisfy the annoying requirement
4042 -- in Ada that there be at least one return, and we certainly do not
4043 -- want to go posting warnings on X that it is not initialized. On
4044 -- the other hand, if X is entirely unreferenced that should still
4045 -- get a warning.
4047 -- What we do is to detect these cases, and if we find them, flag the
4048 -- subprogram as being Is_Trivial_Subprogram and then use that flag to
4049 -- suppress unwanted warnings. For the case of the function stub above
4050 -- we have a special test to set X as apparently assigned to suppress
4051 -- the warning.
4053 declare
4054 Stm : Node_Id;
4056 begin
4057 -- Skip initial labels (for one thing this occurs when we are in
4058 -- front end ZCX mode, but in any case it is irrelevant), and also
4059 -- initial Push_xxx_Error_Label nodes, which are also irrelevant.
4061 Stm := First (Statements (HSS));
4062 while Nkind (Stm) = N_Label
4063 or else Nkind (Stm) in N_Push_xxx_Label
4064 loop
4065 Next (Stm);
4066 end loop;
4068 -- Do the test on the original statement before expansion
4070 declare
4071 Ostm : constant Node_Id := Original_Node (Stm);
4073 begin
4074 -- If explicit raise statement, turn on flag
4076 if Nkind (Ostm) = N_Raise_Statement then
4077 Set_Trivial_Subprogram (Stm);
4079 -- If null statement, and no following statements, turn on flag
4081 elsif Nkind (Stm) = N_Null_Statement
4082 and then Comes_From_Source (Stm)
4083 and then No (Next (Stm))
4084 then
4085 Set_Trivial_Subprogram (Stm);
4087 -- Check for explicit call cases which likely raise an exception
4089 elsif Nkind (Ostm) = N_Procedure_Call_Statement then
4090 if Is_Entity_Name (Name (Ostm)) then
4091 declare
4092 Ent : constant Entity_Id := Entity (Name (Ostm));
4094 begin
4095 -- If the procedure is marked No_Return, then likely it
4096 -- raises an exception, but in any case it is not coming
4097 -- back here, so turn on the flag.
4099 if Present (Ent)
4100 and then Ekind (Ent) = E_Procedure
4101 and then No_Return (Ent)
4102 then
4103 Set_Trivial_Subprogram (Stm);
4104 end if;
4105 end;
4106 end if;
4107 end if;
4108 end;
4109 end;
4111 -- Check for variables that are never modified
4113 declare
4114 E1, E2 : Entity_Id;
4116 begin
4117 -- If there is a separate spec, then transfer Never_Set_In_Source
4118 -- flags from out parameters to the corresponding entities in the
4119 -- body. The reason we do that is we want to post error flags on
4120 -- the body entities, not the spec entities.
4122 if Present (Spec_Id) then
4123 E1 := First_Entity (Spec_Id);
4124 while Present (E1) loop
4125 if Ekind (E1) = E_Out_Parameter then
4126 E2 := First_Entity (Body_Id);
4127 while Present (E2) loop
4128 exit when Chars (E1) = Chars (E2);
4129 Next_Entity (E2);
4130 end loop;
4132 if Present (E2) then
4133 Set_Never_Set_In_Source (E2, Never_Set_In_Source (E1));
4134 end if;
4135 end if;
4137 Next_Entity (E1);
4138 end loop;
4139 end if;
4141 -- Check references in body
4143 Check_References (Body_Id);
4144 end;
4145 end Analyze_Subprogram_Body_Helper;
4147 ---------------------------------
4148 -- Analyze_Subprogram_Contract --
4149 ---------------------------------
4151 procedure Analyze_Subprogram_Contract (Subp : Entity_Id) is
4152 Items : constant Node_Id := Contract (Subp);
4153 Case_Prag : Node_Id := Empty;
4154 Depends : Node_Id := Empty;
4155 Global : Node_Id := Empty;
4156 Mode : SPARK_Mode_Type;
4157 Nam : Name_Id;
4158 Post_Prag : Node_Id := Empty;
4159 Prag : Node_Id;
4160 Seen_In_Case : Boolean := False;
4161 Seen_In_Post : Boolean := False;
4163 begin
4164 -- Due to the timing of contract analysis, delayed pragmas may be
4165 -- subject to the wrong SPARK_Mode, usually that of the enclosing
4166 -- context. To remedy this, restore the original SPARK_Mode of the
4167 -- related subprogram body.
4169 Save_SPARK_Mode_And_Set (Subp, Mode);
4171 if Present (Items) then
4173 -- Analyze pre- and postconditions
4175 Prag := Pre_Post_Conditions (Items);
4176 while Present (Prag) loop
4177 Analyze_Pre_Post_Condition_In_Decl_Part (Prag, Subp);
4179 -- Verify whether a postcondition mentions attribute 'Result and
4180 -- its expression introduces a post-state.
4182 if Warn_On_Suspicious_Contract
4183 and then Pragma_Name (Prag) = Name_Postcondition
4184 then
4185 Post_Prag := Prag;
4186 Check_Result_And_Post_State (Prag, Seen_In_Post);
4187 end if;
4189 Prag := Next_Pragma (Prag);
4190 end loop;
4192 -- Analyze contract-cases and test-cases
4194 Prag := Contract_Test_Cases (Items);
4195 while Present (Prag) loop
4196 Nam := Pragma_Name (Prag);
4198 if Nam = Name_Contract_Cases then
4199 Analyze_Contract_Cases_In_Decl_Part (Prag);
4201 -- Verify whether contract-cases mention attribute 'Result and
4202 -- its expression introduces a post-state. Perform the check
4203 -- only when the pragma is legal.
4205 if Warn_On_Suspicious_Contract
4206 and then not Error_Posted (Prag)
4207 then
4208 Case_Prag := Prag;
4209 Check_Result_And_Post_State (Prag, Seen_In_Case);
4210 end if;
4212 else
4213 pragma Assert (Nam = Name_Test_Case);
4214 Analyze_Test_Case_In_Decl_Part (Prag, Subp);
4215 end if;
4217 Prag := Next_Pragma (Prag);
4218 end loop;
4220 -- Analyze classification pragmas
4222 Prag := Classifications (Items);
4223 while Present (Prag) loop
4224 Nam := Pragma_Name (Prag);
4226 if Nam = Name_Depends then
4227 Depends := Prag;
4229 elsif Nam = Name_Global then
4230 Global := Prag;
4232 -- Note that pragma Extensions_Visible has already been analyzed
4234 end if;
4236 Prag := Next_Pragma (Prag);
4237 end loop;
4239 -- Analyze Global first as Depends may mention items classified in
4240 -- the global categorization.
4242 if Present (Global) then
4243 Analyze_Global_In_Decl_Part (Global);
4244 end if;
4246 -- Depends must be analyzed after Global in order to see the modes of
4247 -- all global items.
4249 if Present (Depends) then
4250 Analyze_Depends_In_Decl_Part (Depends);
4251 end if;
4252 end if;
4254 -- Emit an error when neither the postconditions nor the contract-cases
4255 -- mention attribute 'Result in the context of a function.
4257 if Warn_On_Suspicious_Contract
4258 and then Ekind_In (Subp, E_Function, E_Generic_Function)
4259 then
4260 if Present (Case_Prag)
4261 and then not Seen_In_Case
4262 and then Present (Post_Prag)
4263 and then not Seen_In_Post
4264 then
4265 Error_Msg_N
4266 ("neither function postcondition nor contract cases mention "
4267 & "result?T?", Post_Prag);
4269 elsif Present (Case_Prag) and then not Seen_In_Case then
4270 Error_Msg_N
4271 ("contract cases do not mention result?T?", Case_Prag);
4273 -- OK if we have at least one IN OUT parameter
4275 elsif Present (Post_Prag) and then not Seen_In_Post then
4276 declare
4277 F : Entity_Id;
4278 begin
4279 F := First_Formal (Subp);
4280 while Present (F) loop
4281 if Ekind (F) = E_In_Out_Parameter then
4282 return;
4283 else
4284 Next_Formal (F);
4285 end if;
4286 end loop;
4287 end;
4289 -- If no in-out parameters and no mention of Result, the contract
4290 -- is certainly suspicious.
4292 Error_Msg_N
4293 ("function postcondition does not mention result?T?", Post_Prag);
4294 end if;
4295 end if;
4297 -- Restore the SPARK_Mode of the enclosing context after all delayed
4298 -- pragmas have been analyzed.
4300 Restore_SPARK_Mode (Mode);
4301 end Analyze_Subprogram_Contract;
4303 ------------------------------------
4304 -- Analyze_Subprogram_Declaration --
4305 ------------------------------------
4307 procedure Analyze_Subprogram_Declaration (N : Node_Id) is
4308 Scop : constant Entity_Id := Current_Scope;
4309 Designator : Entity_Id;
4311 Is_Completion : Boolean;
4312 -- Indicates whether a null procedure declaration is a completion
4314 begin
4315 -- The subprogram declaration may be subject to pragma Ghost with policy
4316 -- Ignore. Set the mode now to ensure that any nodes generated during
4317 -- analysis and expansion are properly flagged as ignored Ghost.
4319 Set_Ghost_Mode (N);
4321 -- Null procedures are not allowed in SPARK
4323 if Nkind (Specification (N)) = N_Procedure_Specification
4324 and then Null_Present (Specification (N))
4325 then
4326 Check_SPARK_05_Restriction ("null procedure is not allowed", N);
4328 if Is_Protected_Type (Current_Scope) then
4329 Error_Msg_N ("protected operation cannot be a null procedure", N);
4330 end if;
4332 Analyze_Null_Procedure (N, Is_Completion);
4334 if Is_Completion then
4336 -- The null procedure acts as a body, nothing further is needed.
4338 return;
4339 end if;
4340 end if;
4342 Designator := Analyze_Subprogram_Specification (Specification (N));
4344 -- A reference may already have been generated for the unit name, in
4345 -- which case the following call is redundant. However it is needed for
4346 -- declarations that are the rewriting of an expression function.
4348 Generate_Definition (Designator);
4350 -- Set SPARK mode from current context (may be overwritten later with
4351 -- explicit pragma).
4353 Set_SPARK_Pragma (Designator, SPARK_Mode_Pragma);
4354 Set_SPARK_Pragma_Inherited (Designator);
4356 -- A subprogram declared within a Ghost region is automatically Ghost
4357 -- (SPARK RM 6.9(2)).
4359 if Comes_From_Source (Designator) and then Ghost_Mode > None then
4360 Set_Is_Ghost_Entity (Designator);
4361 end if;
4363 if Debug_Flag_C then
4364 Write_Str ("==> subprogram spec ");
4365 Write_Name (Chars (Designator));
4366 Write_Str (" from ");
4367 Write_Location (Sloc (N));
4368 Write_Eol;
4369 Indent;
4370 end if;
4372 Validate_RCI_Subprogram_Declaration (N);
4373 New_Overloaded_Entity (Designator);
4374 Check_Delayed_Subprogram (Designator);
4376 -- If the type of the first formal of the current subprogram is a non-
4377 -- generic tagged private type, mark the subprogram as being a private
4378 -- primitive. Ditto if this is a function with controlling result, and
4379 -- the return type is currently private. In both cases, the type of the
4380 -- controlling argument or result must be in the current scope for the
4381 -- operation to be primitive.
4383 if Has_Controlling_Result (Designator)
4384 and then Is_Private_Type (Etype (Designator))
4385 and then Scope (Etype (Designator)) = Current_Scope
4386 and then not Is_Generic_Actual_Type (Etype (Designator))
4387 then
4388 Set_Is_Private_Primitive (Designator);
4390 elsif Present (First_Formal (Designator)) then
4391 declare
4392 Formal_Typ : constant Entity_Id :=
4393 Etype (First_Formal (Designator));
4394 begin
4395 Set_Is_Private_Primitive (Designator,
4396 Is_Tagged_Type (Formal_Typ)
4397 and then Scope (Formal_Typ) = Current_Scope
4398 and then Is_Private_Type (Formal_Typ)
4399 and then not Is_Generic_Actual_Type (Formal_Typ));
4400 end;
4401 end if;
4403 -- Ada 2005 (AI-251): Abstract interface primitives must be abstract
4404 -- or null.
4406 if Ada_Version >= Ada_2005
4407 and then Comes_From_Source (N)
4408 and then Is_Dispatching_Operation (Designator)
4409 then
4410 declare
4411 E : Entity_Id;
4412 Etyp : Entity_Id;
4414 begin
4415 if Has_Controlling_Result (Designator) then
4416 Etyp := Etype (Designator);
4418 else
4419 E := First_Entity (Designator);
4420 while Present (E)
4421 and then Is_Formal (E)
4422 and then not Is_Controlling_Formal (E)
4423 loop
4424 Next_Entity (E);
4425 end loop;
4427 Etyp := Etype (E);
4428 end if;
4430 if Is_Access_Type (Etyp) then
4431 Etyp := Directly_Designated_Type (Etyp);
4432 end if;
4434 if Is_Interface (Etyp)
4435 and then not Is_Abstract_Subprogram (Designator)
4436 and then not (Ekind (Designator) = E_Procedure
4437 and then Null_Present (Specification (N)))
4438 then
4439 Error_Msg_Name_1 := Chars (Defining_Entity (N));
4441 -- Specialize error message based on procedures vs. functions,
4442 -- since functions can't be null subprograms.
4444 if Ekind (Designator) = E_Procedure then
4445 Error_Msg_N
4446 ("interface procedure % must be abstract or null", N);
4447 else
4448 Error_Msg_N
4449 ("interface function % must be abstract", N);
4450 end if;
4451 end if;
4452 end;
4453 end if;
4455 -- What is the following code for, it used to be
4457 -- ??? Set_Suppress_Elaboration_Checks
4458 -- ??? (Designator, Elaboration_Checks_Suppressed (Designator));
4460 -- The following seems equivalent, but a bit dubious
4462 if Elaboration_Checks_Suppressed (Designator) then
4463 Set_Kill_Elaboration_Checks (Designator);
4464 end if;
4466 if Scop /= Standard_Standard and then not Is_Child_Unit (Designator) then
4467 Set_Categorization_From_Scope (Designator, Scop);
4469 else
4470 -- For a compilation unit, check for library-unit pragmas
4472 Push_Scope (Designator);
4473 Set_Categorization_From_Pragmas (N);
4474 Validate_Categorization_Dependency (N, Designator);
4475 Pop_Scope;
4476 end if;
4478 -- For a compilation unit, set body required. This flag will only be
4479 -- reset if a valid Import or Interface pragma is processed later on.
4481 if Nkind (Parent (N)) = N_Compilation_Unit then
4482 Set_Body_Required (Parent (N), True);
4484 if Ada_Version >= Ada_2005
4485 and then Nkind (Specification (N)) = N_Procedure_Specification
4486 and then Null_Present (Specification (N))
4487 then
4488 Error_Msg_N
4489 ("null procedure cannot be declared at library level", N);
4490 end if;
4491 end if;
4493 Generate_Reference_To_Formals (Designator);
4494 Check_Eliminated (Designator);
4496 if Debug_Flag_C then
4497 Outdent;
4498 Write_Str ("<== subprogram spec ");
4499 Write_Name (Chars (Designator));
4500 Write_Str (" from ");
4501 Write_Location (Sloc (N));
4502 Write_Eol;
4503 end if;
4505 if Is_Protected_Type (Current_Scope) then
4507 -- Indicate that this is a protected operation, because it may be
4508 -- used in subsequent declarations within the protected type.
4510 Set_Convention (Designator, Convention_Protected);
4511 end if;
4513 List_Inherited_Pre_Post_Aspects (Designator);
4515 if Has_Aspects (N) then
4516 Analyze_Aspect_Specifications (N, Designator);
4517 end if;
4518 end Analyze_Subprogram_Declaration;
4520 --------------------------------------
4521 -- Analyze_Subprogram_Specification --
4522 --------------------------------------
4524 -- Reminder: N here really is a subprogram specification (not a subprogram
4525 -- declaration). This procedure is called to analyze the specification in
4526 -- both subprogram bodies and subprogram declarations (specs).
4528 function Analyze_Subprogram_Specification (N : Node_Id) return Entity_Id is
4529 Designator : constant Entity_Id := Defining_Entity (N);
4530 Formals : constant List_Id := Parameter_Specifications (N);
4532 -- Start of processing for Analyze_Subprogram_Specification
4534 begin
4535 -- User-defined operator is not allowed in SPARK, except as a renaming
4537 if Nkind (Defining_Unit_Name (N)) = N_Defining_Operator_Symbol
4538 and then Nkind (Parent (N)) /= N_Subprogram_Renaming_Declaration
4539 then
4540 Check_SPARK_05_Restriction
4541 ("user-defined operator is not allowed", N);
4542 end if;
4544 -- Proceed with analysis. Do not emit a cross-reference entry if the
4545 -- specification comes from an expression function, because it may be
4546 -- the completion of a previous declaration. It is is not, the cross-
4547 -- reference entry will be emitted for the new subprogram declaration.
4549 if Nkind (Parent (N)) /= N_Expression_Function then
4550 Generate_Definition (Designator);
4551 end if;
4553 Set_Contract (Designator, Make_Contract (Sloc (Designator)));
4555 if Nkind (N) = N_Function_Specification then
4556 Set_Ekind (Designator, E_Function);
4557 Set_Mechanism (Designator, Default_Mechanism);
4558 else
4559 Set_Ekind (Designator, E_Procedure);
4560 Set_Etype (Designator, Standard_Void_Type);
4561 end if;
4563 -- Flag Is_Inlined_Always is True by default, and reversed to False for
4564 -- those subprograms which could be inlined in GNATprove mode (because
4565 -- Body_To_Inline is non-Empty) but cannot be inlined.
4567 if GNATprove_Mode then
4568 Set_Is_Inlined_Always (Designator);
4569 end if;
4571 -- Introduce new scope for analysis of the formals and the return type
4573 Set_Scope (Designator, Current_Scope);
4575 if Present (Formals) then
4576 Push_Scope (Designator);
4577 Process_Formals (Formals, N);
4579 -- Check dimensions in N for formals with default expression
4581 Analyze_Dimension_Formals (N, Formals);
4583 -- Ada 2005 (AI-345): If this is an overriding operation of an
4584 -- inherited interface operation, and the controlling type is
4585 -- a synchronized type, replace the type with its corresponding
4586 -- record, to match the proper signature of an overriding operation.
4587 -- Same processing for an access parameter whose designated type is
4588 -- derived from a synchronized interface.
4590 if Ada_Version >= Ada_2005 then
4591 declare
4592 Formal : Entity_Id;
4593 Formal_Typ : Entity_Id;
4594 Rec_Typ : Entity_Id;
4595 Desig_Typ : Entity_Id;
4597 begin
4598 Formal := First_Formal (Designator);
4599 while Present (Formal) loop
4600 Formal_Typ := Etype (Formal);
4602 if Is_Concurrent_Type (Formal_Typ)
4603 and then Present (Corresponding_Record_Type (Formal_Typ))
4604 then
4605 Rec_Typ := Corresponding_Record_Type (Formal_Typ);
4607 if Present (Interfaces (Rec_Typ)) then
4608 Set_Etype (Formal, Rec_Typ);
4609 end if;
4611 elsif Ekind (Formal_Typ) = E_Anonymous_Access_Type then
4612 Desig_Typ := Designated_Type (Formal_Typ);
4614 if Is_Concurrent_Type (Desig_Typ)
4615 and then Present (Corresponding_Record_Type (Desig_Typ))
4616 then
4617 Rec_Typ := Corresponding_Record_Type (Desig_Typ);
4619 if Present (Interfaces (Rec_Typ)) then
4620 Set_Directly_Designated_Type (Formal_Typ, Rec_Typ);
4621 end if;
4622 end if;
4623 end if;
4625 Next_Formal (Formal);
4626 end loop;
4627 end;
4628 end if;
4630 End_Scope;
4632 -- The subprogram scope is pushed and popped around the processing of
4633 -- the return type for consistency with call above to Process_Formals
4634 -- (which itself can call Analyze_Return_Type), and to ensure that any
4635 -- itype created for the return type will be associated with the proper
4636 -- scope.
4638 elsif Nkind (N) = N_Function_Specification then
4639 Push_Scope (Designator);
4640 Analyze_Return_Type (N);
4641 End_Scope;
4642 end if;
4644 -- Function case
4646 if Nkind (N) = N_Function_Specification then
4648 -- Deal with operator symbol case
4650 if Nkind (Designator) = N_Defining_Operator_Symbol then
4651 Valid_Operator_Definition (Designator);
4652 end if;
4654 May_Need_Actuals (Designator);
4656 -- Ada 2005 (AI-251): If the return type is abstract, verify that
4657 -- the subprogram is abstract also. This does not apply to renaming
4658 -- declarations, where abstractness is inherited, and to subprogram
4659 -- bodies generated for stream operations, which become renamings as
4660 -- bodies.
4662 -- In case of primitives associated with abstract interface types
4663 -- the check is applied later (see Analyze_Subprogram_Declaration).
4665 if not Nkind_In (Original_Node (Parent (N)),
4666 N_Subprogram_Renaming_Declaration,
4667 N_Abstract_Subprogram_Declaration,
4668 N_Formal_Abstract_Subprogram_Declaration)
4669 then
4670 if Is_Abstract_Type (Etype (Designator))
4671 and then not Is_Interface (Etype (Designator))
4672 then
4673 Error_Msg_N
4674 ("function that returns abstract type must be abstract", N);
4676 -- Ada 2012 (AI-0073): Extend this test to subprograms with an
4677 -- access result whose designated type is abstract.
4679 elsif Nkind (Result_Definition (N)) = N_Access_Definition
4680 and then
4681 not Is_Class_Wide_Type (Designated_Type (Etype (Designator)))
4682 and then Is_Abstract_Type (Designated_Type (Etype (Designator)))
4683 and then Ada_Version >= Ada_2012
4684 then
4685 Error_Msg_N ("function whose access result designates "
4686 & "abstract type must be abstract", N);
4687 end if;
4688 end if;
4689 end if;
4691 return Designator;
4692 end Analyze_Subprogram_Specification;
4694 -----------------------
4695 -- Check_Conformance --
4696 -----------------------
4698 procedure Check_Conformance
4699 (New_Id : Entity_Id;
4700 Old_Id : Entity_Id;
4701 Ctype : Conformance_Type;
4702 Errmsg : Boolean;
4703 Conforms : out Boolean;
4704 Err_Loc : Node_Id := Empty;
4705 Get_Inst : Boolean := False;
4706 Skip_Controlling_Formals : Boolean := False)
4708 procedure Conformance_Error (Msg : String; N : Node_Id := New_Id);
4709 -- Sets Conforms to False. If Errmsg is False, then that's all it does.
4710 -- If Errmsg is True, then processing continues to post an error message
4711 -- for conformance error on given node. Two messages are output. The
4712 -- first message points to the previous declaration with a general "no
4713 -- conformance" message. The second is the detailed reason, supplied as
4714 -- Msg. The parameter N provide information for a possible & insertion
4715 -- in the message, and also provides the location for posting the
4716 -- message in the absence of a specified Err_Loc location.
4718 -----------------------
4719 -- Conformance_Error --
4720 -----------------------
4722 procedure Conformance_Error (Msg : String; N : Node_Id := New_Id) is
4723 Enode : Node_Id;
4725 begin
4726 Conforms := False;
4728 if Errmsg then
4729 if No (Err_Loc) then
4730 Enode := N;
4731 else
4732 Enode := Err_Loc;
4733 end if;
4735 Error_Msg_Sloc := Sloc (Old_Id);
4737 case Ctype is
4738 when Type_Conformant =>
4739 Error_Msg_N -- CODEFIX
4740 ("not type conformant with declaration#!", Enode);
4742 when Mode_Conformant =>
4743 if Nkind (Parent (Old_Id)) = N_Full_Type_Declaration then
4744 Error_Msg_N
4745 ("not mode conformant with operation inherited#!",
4746 Enode);
4747 else
4748 Error_Msg_N
4749 ("not mode conformant with declaration#!", Enode);
4750 end if;
4752 when Subtype_Conformant =>
4753 if Nkind (Parent (Old_Id)) = N_Full_Type_Declaration then
4754 Error_Msg_N
4755 ("not subtype conformant with operation inherited#!",
4756 Enode);
4757 else
4758 Error_Msg_N
4759 ("not subtype conformant with declaration#!", Enode);
4760 end if;
4762 when Fully_Conformant =>
4763 if Nkind (Parent (Old_Id)) = N_Full_Type_Declaration then
4764 Error_Msg_N -- CODEFIX
4765 ("not fully conformant with operation inherited#!",
4766 Enode);
4767 else
4768 Error_Msg_N -- CODEFIX
4769 ("not fully conformant with declaration#!", Enode);
4770 end if;
4771 end case;
4773 Error_Msg_NE (Msg, Enode, N);
4774 end if;
4775 end Conformance_Error;
4777 -- Local Variables
4779 Old_Type : constant Entity_Id := Etype (Old_Id);
4780 New_Type : constant Entity_Id := Etype (New_Id);
4781 Old_Formal : Entity_Id;
4782 New_Formal : Entity_Id;
4783 Access_Types_Match : Boolean;
4784 Old_Formal_Base : Entity_Id;
4785 New_Formal_Base : Entity_Id;
4787 -- Start of processing for Check_Conformance
4789 begin
4790 Conforms := True;
4792 -- We need a special case for operators, since they don't appear
4793 -- explicitly.
4795 if Ctype = Type_Conformant then
4796 if Ekind (New_Id) = E_Operator
4797 and then Operator_Matches_Spec (New_Id, Old_Id)
4798 then
4799 return;
4800 end if;
4801 end if;
4803 -- If both are functions/operators, check return types conform
4805 if Old_Type /= Standard_Void_Type
4806 and then
4807 New_Type /= Standard_Void_Type
4808 then
4809 -- If we are checking interface conformance we omit controlling
4810 -- arguments and result, because we are only checking the conformance
4811 -- of the remaining parameters.
4813 if Has_Controlling_Result (Old_Id)
4814 and then Has_Controlling_Result (New_Id)
4815 and then Skip_Controlling_Formals
4816 then
4817 null;
4819 elsif not Conforming_Types (Old_Type, New_Type, Ctype, Get_Inst) then
4820 if Ctype >= Subtype_Conformant
4821 and then not Predicates_Match (Old_Type, New_Type)
4822 then
4823 Conformance_Error
4824 ("\predicate of return type does not match!", New_Id);
4825 else
4826 Conformance_Error
4827 ("\return type does not match!", New_Id);
4828 end if;
4830 return;
4831 end if;
4833 -- Ada 2005 (AI-231): In case of anonymous access types check the
4834 -- null-exclusion and access-to-constant attributes match.
4836 if Ada_Version >= Ada_2005
4837 and then Ekind (Etype (Old_Type)) = E_Anonymous_Access_Type
4838 and then
4839 (Can_Never_Be_Null (Old_Type) /= Can_Never_Be_Null (New_Type)
4840 or else Is_Access_Constant (Etype (Old_Type)) /=
4841 Is_Access_Constant (Etype (New_Type)))
4842 then
4843 Conformance_Error ("\return type does not match!", New_Id);
4844 return;
4845 end if;
4847 -- If either is a function/operator and the other isn't, error
4849 elsif Old_Type /= Standard_Void_Type
4850 or else New_Type /= Standard_Void_Type
4851 then
4852 Conformance_Error ("\functions can only match functions!", New_Id);
4853 return;
4854 end if;
4856 -- In subtype conformant case, conventions must match (RM 6.3.1(16)).
4857 -- If this is a renaming as body, refine error message to indicate that
4858 -- the conflict is with the original declaration. If the entity is not
4859 -- frozen, the conventions don't have to match, the one of the renamed
4860 -- entity is inherited.
4862 if Ctype >= Subtype_Conformant then
4863 if Convention (Old_Id) /= Convention (New_Id) then
4864 if not Is_Frozen (New_Id) then
4865 null;
4867 elsif Present (Err_Loc)
4868 and then Nkind (Err_Loc) = N_Subprogram_Renaming_Declaration
4869 and then Present (Corresponding_Spec (Err_Loc))
4870 then
4871 Error_Msg_Name_1 := Chars (New_Id);
4872 Error_Msg_Name_2 :=
4873 Name_Ada + Convention_Id'Pos (Convention (New_Id));
4874 Conformance_Error ("\prior declaration for% has convention %!");
4876 else
4877 Conformance_Error ("\calling conventions do not match!");
4878 end if;
4880 return;
4882 elsif Is_Formal_Subprogram (Old_Id)
4883 or else Is_Formal_Subprogram (New_Id)
4884 then
4885 Conformance_Error ("\formal subprograms not allowed!");
4886 return;
4888 -- Pragma Ghost behaves as a convention in the context of subtype
4889 -- conformance (SPARK RM 6.9(5)). Do not check internally generated
4890 -- subprograms as their spec may reside in a Ghost region and their
4891 -- body not, or vice versa.
4893 elsif Comes_From_Source (Old_Id)
4894 and then Comes_From_Source (New_Id)
4895 and then Is_Ghost_Entity (Old_Id) /= Is_Ghost_Entity (New_Id)
4896 then
4897 Conformance_Error ("\ghost modes do not match!");
4898 return;
4899 end if;
4900 end if;
4902 -- Deal with parameters
4904 -- Note: we use the entity information, rather than going directly
4905 -- to the specification in the tree. This is not only simpler, but
4906 -- absolutely necessary for some cases of conformance tests between
4907 -- operators, where the declaration tree simply does not exist.
4909 Old_Formal := First_Formal (Old_Id);
4910 New_Formal := First_Formal (New_Id);
4911 while Present (Old_Formal) and then Present (New_Formal) loop
4912 if Is_Controlling_Formal (Old_Formal)
4913 and then Is_Controlling_Formal (New_Formal)
4914 and then Skip_Controlling_Formals
4915 then
4916 -- The controlling formals will have different types when
4917 -- comparing an interface operation with its match, but both
4918 -- or neither must be access parameters.
4920 if Is_Access_Type (Etype (Old_Formal))
4922 Is_Access_Type (Etype (New_Formal))
4923 then
4924 goto Skip_Controlling_Formal;
4925 else
4926 Conformance_Error
4927 ("\access parameter does not match!", New_Formal);
4928 end if;
4929 end if;
4931 -- Ada 2012: Mode conformance also requires that formal parameters
4932 -- be both aliased, or neither.
4934 if Ctype >= Mode_Conformant and then Ada_Version >= Ada_2012 then
4935 if Is_Aliased (Old_Formal) /= Is_Aliased (New_Formal) then
4936 Conformance_Error
4937 ("\aliased parameter mismatch!", New_Formal);
4938 end if;
4939 end if;
4941 if Ctype = Fully_Conformant then
4943 -- Names must match. Error message is more accurate if we do
4944 -- this before checking that the types of the formals match.
4946 if Chars (Old_Formal) /= Chars (New_Formal) then
4947 Conformance_Error ("\name& does not match!", New_Formal);
4949 -- Set error posted flag on new formal as well to stop
4950 -- junk cascaded messages in some cases.
4952 Set_Error_Posted (New_Formal);
4953 return;
4954 end if;
4956 -- Null exclusion must match
4958 if Null_Exclusion_Present (Parent (Old_Formal))
4960 Null_Exclusion_Present (Parent (New_Formal))
4961 then
4962 -- Only give error if both come from source. This should be
4963 -- investigated some time, since it should not be needed ???
4965 if Comes_From_Source (Old_Formal)
4966 and then
4967 Comes_From_Source (New_Formal)
4968 then
4969 Conformance_Error
4970 ("\null exclusion for& does not match", New_Formal);
4972 -- Mark error posted on the new formal to avoid duplicated
4973 -- complaint about types not matching.
4975 Set_Error_Posted (New_Formal);
4976 end if;
4977 end if;
4978 end if;
4980 -- Ada 2005 (AI-423): Possible access [sub]type and itype match. This
4981 -- case occurs whenever a subprogram is being renamed and one of its
4982 -- parameters imposes a null exclusion. For example:
4984 -- type T is null record;
4985 -- type Acc_T is access T;
4986 -- subtype Acc_T_Sub is Acc_T;
4988 -- procedure P (Obj : not null Acc_T_Sub); -- itype
4989 -- procedure Ren_P (Obj : Acc_T_Sub) -- subtype
4990 -- renames P;
4992 Old_Formal_Base := Etype (Old_Formal);
4993 New_Formal_Base := Etype (New_Formal);
4995 if Get_Inst then
4996 Old_Formal_Base := Get_Instance_Of (Old_Formal_Base);
4997 New_Formal_Base := Get_Instance_Of (New_Formal_Base);
4998 end if;
5000 Access_Types_Match := Ada_Version >= Ada_2005
5002 -- Ensure that this rule is only applied when New_Id is a
5003 -- renaming of Old_Id.
5005 and then Nkind (Parent (Parent (New_Id))) =
5006 N_Subprogram_Renaming_Declaration
5007 and then Nkind (Name (Parent (Parent (New_Id)))) in N_Has_Entity
5008 and then Present (Entity (Name (Parent (Parent (New_Id)))))
5009 and then Entity (Name (Parent (Parent (New_Id)))) = Old_Id
5011 -- Now handle the allowed access-type case
5013 and then Is_Access_Type (Old_Formal_Base)
5014 and then Is_Access_Type (New_Formal_Base)
5016 -- The type kinds must match. The only exception occurs with
5017 -- multiple generics of the form:
5019 -- generic generic
5020 -- type F is private; type A is private;
5021 -- type F_Ptr is access F; type A_Ptr is access A;
5022 -- with proc F_P (X : F_Ptr); with proc A_P (X : A_Ptr);
5023 -- package F_Pack is ... package A_Pack is
5024 -- package F_Inst is
5025 -- new F_Pack (A, A_Ptr, A_P);
5027 -- When checking for conformance between the parameters of A_P
5028 -- and F_P, the type kinds of F_Ptr and A_Ptr will not match
5029 -- because the compiler has transformed A_Ptr into a subtype of
5030 -- F_Ptr. We catch this case in the code below.
5032 and then (Ekind (Old_Formal_Base) = Ekind (New_Formal_Base)
5033 or else
5034 (Is_Generic_Type (Old_Formal_Base)
5035 and then Is_Generic_Type (New_Formal_Base)
5036 and then Is_Internal (New_Formal_Base)
5037 and then Etype (Etype (New_Formal_Base)) =
5038 Old_Formal_Base))
5039 and then Directly_Designated_Type (Old_Formal_Base) =
5040 Directly_Designated_Type (New_Formal_Base)
5041 and then ((Is_Itype (Old_Formal_Base)
5042 and then Can_Never_Be_Null (Old_Formal_Base))
5043 or else
5044 (Is_Itype (New_Formal_Base)
5045 and then Can_Never_Be_Null (New_Formal_Base)));
5047 -- Types must always match. In the visible part of an instance,
5048 -- usual overloading rules for dispatching operations apply, and
5049 -- we check base types (not the actual subtypes).
5051 if In_Instance_Visible_Part
5052 and then Is_Dispatching_Operation (New_Id)
5053 then
5054 if not Conforming_Types
5055 (T1 => Base_Type (Etype (Old_Formal)),
5056 T2 => Base_Type (Etype (New_Formal)),
5057 Ctype => Ctype,
5058 Get_Inst => Get_Inst)
5059 and then not Access_Types_Match
5060 then
5061 Conformance_Error ("\type of & does not match!", New_Formal);
5062 return;
5063 end if;
5065 elsif not Conforming_Types
5066 (T1 => Old_Formal_Base,
5067 T2 => New_Formal_Base,
5068 Ctype => Ctype,
5069 Get_Inst => Get_Inst)
5070 and then not Access_Types_Match
5071 then
5072 -- Don't give error message if old type is Any_Type. This test
5073 -- avoids some cascaded errors, e.g. in case of a bad spec.
5075 if Errmsg and then Old_Formal_Base = Any_Type then
5076 Conforms := False;
5077 else
5078 if Ctype >= Subtype_Conformant
5079 and then
5080 not Predicates_Match (Old_Formal_Base, New_Formal_Base)
5081 then
5082 Conformance_Error
5083 ("\predicate of & does not match!", New_Formal);
5084 else
5085 Conformance_Error
5086 ("\type of & does not match!", New_Formal);
5087 end if;
5088 end if;
5090 return;
5091 end if;
5093 -- For mode conformance, mode must match
5095 if Ctype >= Mode_Conformant then
5096 if Parameter_Mode (Old_Formal) /= Parameter_Mode (New_Formal) then
5097 if not Ekind_In (New_Id, E_Function, E_Procedure)
5098 or else not Is_Primitive_Wrapper (New_Id)
5099 then
5100 Conformance_Error ("\mode of & does not match!", New_Formal);
5102 else
5103 declare
5104 T : constant Entity_Id := Find_Dispatching_Type (New_Id);
5105 begin
5106 if Is_Protected_Type (Corresponding_Concurrent_Type (T))
5107 then
5108 Error_Msg_PT (T, New_Id);
5109 else
5110 Conformance_Error
5111 ("\mode of & does not match!", New_Formal);
5112 end if;
5113 end;
5114 end if;
5116 return;
5118 -- Part of mode conformance for access types is having the same
5119 -- constant modifier.
5121 elsif Access_Types_Match
5122 and then Is_Access_Constant (Old_Formal_Base) /=
5123 Is_Access_Constant (New_Formal_Base)
5124 then
5125 Conformance_Error
5126 ("\constant modifier does not match!", New_Formal);
5127 return;
5128 end if;
5129 end if;
5131 if Ctype >= Subtype_Conformant then
5133 -- Ada 2005 (AI-231): In case of anonymous access types check
5134 -- the null-exclusion and access-to-constant attributes must
5135 -- match. For null exclusion, we test the types rather than the
5136 -- formals themselves, since the attribute is only set reliably
5137 -- on the formals in the Ada 95 case, and we exclude the case
5138 -- where Old_Formal is marked as controlling, to avoid errors
5139 -- when matching completing bodies with dispatching declarations
5140 -- (access formals in the bodies aren't marked Can_Never_Be_Null).
5142 if Ada_Version >= Ada_2005
5143 and then Ekind (Etype (Old_Formal)) = E_Anonymous_Access_Type
5144 and then Ekind (Etype (New_Formal)) = E_Anonymous_Access_Type
5145 and then
5146 ((Can_Never_Be_Null (Etype (Old_Formal)) /=
5147 Can_Never_Be_Null (Etype (New_Formal))
5148 and then
5149 not Is_Controlling_Formal (Old_Formal))
5150 or else
5151 Is_Access_Constant (Etype (Old_Formal)) /=
5152 Is_Access_Constant (Etype (New_Formal)))
5154 -- Do not complain if error already posted on New_Formal. This
5155 -- avoids some redundant error messages.
5157 and then not Error_Posted (New_Formal)
5158 then
5159 -- It is allowed to omit the null-exclusion in case of stream
5160 -- attribute subprograms. We recognize stream subprograms
5161 -- through their TSS-generated suffix.
5163 declare
5164 TSS_Name : constant TSS_Name_Type := Get_TSS_Name (New_Id);
5166 begin
5167 if TSS_Name /= TSS_Stream_Read
5168 and then TSS_Name /= TSS_Stream_Write
5169 and then TSS_Name /= TSS_Stream_Input
5170 and then TSS_Name /= TSS_Stream_Output
5171 then
5172 -- Here we have a definite conformance error. It is worth
5173 -- special casing the error message for the case of a
5174 -- controlling formal (which excludes null).
5176 if Is_Controlling_Formal (New_Formal) then
5177 Error_Msg_Node_2 := Scope (New_Formal);
5178 Conformance_Error
5179 ("\controlling formal & of & excludes null, "
5180 & "declaration must exclude null as well",
5181 New_Formal);
5183 -- Normal case (couldn't we give more detail here???)
5185 else
5186 Conformance_Error
5187 ("\type of & does not match!", New_Formal);
5188 end if;
5190 return;
5191 end if;
5192 end;
5193 end if;
5194 end if;
5196 -- Full conformance checks
5198 if Ctype = Fully_Conformant then
5200 -- We have checked already that names match
5202 if Parameter_Mode (Old_Formal) = E_In_Parameter then
5204 -- Check default expressions for in parameters
5206 declare
5207 NewD : constant Boolean :=
5208 Present (Default_Value (New_Formal));
5209 OldD : constant Boolean :=
5210 Present (Default_Value (Old_Formal));
5211 begin
5212 if NewD or OldD then
5214 -- The old default value has been analyzed because the
5215 -- current full declaration will have frozen everything
5216 -- before. The new default value has not been analyzed,
5217 -- so analyze it now before we check for conformance.
5219 if NewD then
5220 Push_Scope (New_Id);
5221 Preanalyze_Spec_Expression
5222 (Default_Value (New_Formal), Etype (New_Formal));
5223 End_Scope;
5224 end if;
5226 if not (NewD and OldD)
5227 or else not Fully_Conformant_Expressions
5228 (Default_Value (Old_Formal),
5229 Default_Value (New_Formal))
5230 then
5231 Conformance_Error
5232 ("\default expression for & does not match!",
5233 New_Formal);
5234 return;
5235 end if;
5236 end if;
5237 end;
5238 end if;
5239 end if;
5241 -- A couple of special checks for Ada 83 mode. These checks are
5242 -- skipped if either entity is an operator in package Standard,
5243 -- or if either old or new instance is not from the source program.
5245 if Ada_Version = Ada_83
5246 and then Sloc (Old_Id) > Standard_Location
5247 and then Sloc (New_Id) > Standard_Location
5248 and then Comes_From_Source (Old_Id)
5249 and then Comes_From_Source (New_Id)
5250 then
5251 declare
5252 Old_Param : constant Node_Id := Declaration_Node (Old_Formal);
5253 New_Param : constant Node_Id := Declaration_Node (New_Formal);
5255 begin
5256 -- Explicit IN must be present or absent in both cases. This
5257 -- test is required only in the full conformance case.
5259 if In_Present (Old_Param) /= In_Present (New_Param)
5260 and then Ctype = Fully_Conformant
5261 then
5262 Conformance_Error
5263 ("\(Ada 83) IN must appear in both declarations",
5264 New_Formal);
5265 return;
5266 end if;
5268 -- Grouping (use of comma in param lists) must be the same
5269 -- This is where we catch a misconformance like:
5271 -- A, B : Integer
5272 -- A : Integer; B : Integer
5274 -- which are represented identically in the tree except
5275 -- for the setting of the flags More_Ids and Prev_Ids.
5277 if More_Ids (Old_Param) /= More_Ids (New_Param)
5278 or else Prev_Ids (Old_Param) /= Prev_Ids (New_Param)
5279 then
5280 Conformance_Error
5281 ("\grouping of & does not match!", New_Formal);
5282 return;
5283 end if;
5284 end;
5285 end if;
5287 -- This label is required when skipping controlling formals
5289 <<Skip_Controlling_Formal>>
5291 Next_Formal (Old_Formal);
5292 Next_Formal (New_Formal);
5293 end loop;
5295 if Present (Old_Formal) then
5296 Conformance_Error ("\too few parameters!");
5297 return;
5299 elsif Present (New_Formal) then
5300 Conformance_Error ("\too many parameters!", New_Formal);
5301 return;
5302 end if;
5303 end Check_Conformance;
5305 -----------------------
5306 -- Check_Conventions --
5307 -----------------------
5309 procedure Check_Conventions (Typ : Entity_Id) is
5310 Ifaces_List : Elist_Id;
5312 procedure Check_Convention (Op : Entity_Id);
5313 -- Verify that the convention of inherited dispatching operation Op is
5314 -- consistent among all subprograms it overrides. In order to minimize
5315 -- the search, Search_From is utilized to designate a specific point in
5316 -- the list rather than iterating over the whole list once more.
5318 ----------------------
5319 -- Check_Convention --
5320 ----------------------
5322 procedure Check_Convention (Op : Entity_Id) is
5323 Op_Conv : constant Convention_Id := Convention (Op);
5324 Iface_Conv : Convention_Id;
5325 Iface_Elmt : Elmt_Id;
5326 Iface_Prim_Elmt : Elmt_Id;
5327 Iface_Prim : Entity_Id;
5329 begin
5330 Iface_Elmt := First_Elmt (Ifaces_List);
5331 while Present (Iface_Elmt) loop
5332 Iface_Prim_Elmt :=
5333 First_Elmt (Primitive_Operations (Node (Iface_Elmt)));
5334 while Present (Iface_Prim_Elmt) loop
5335 Iface_Prim := Node (Iface_Prim_Elmt);
5336 Iface_Conv := Convention (Iface_Prim);
5338 if Is_Interface_Conformant (Typ, Iface_Prim, Op)
5339 and then Iface_Conv /= Op_Conv
5340 then
5341 Error_Msg_N
5342 ("inconsistent conventions in primitive operations", Typ);
5344 Error_Msg_Name_1 := Chars (Op);
5345 Error_Msg_Name_2 := Get_Convention_Name (Op_Conv);
5346 Error_Msg_Sloc := Sloc (Op);
5348 if Comes_From_Source (Op) or else No (Alias (Op)) then
5349 if not Present (Overridden_Operation (Op)) then
5350 Error_Msg_N ("\\primitive % defined #", Typ);
5351 else
5352 Error_Msg_N
5353 ("\\overriding operation % with "
5354 & "convention % defined #", Typ);
5355 end if;
5357 else pragma Assert (Present (Alias (Op)));
5358 Error_Msg_Sloc := Sloc (Alias (Op));
5359 Error_Msg_N ("\\inherited operation % with "
5360 & "convention % defined #", Typ);
5361 end if;
5363 Error_Msg_Name_1 := Chars (Op);
5364 Error_Msg_Name_2 := Get_Convention_Name (Iface_Conv);
5365 Error_Msg_Sloc := Sloc (Iface_Prim);
5366 Error_Msg_N ("\\overridden operation % with "
5367 & "convention % defined #", Typ);
5369 -- Avoid cascading errors
5371 return;
5372 end if;
5374 Next_Elmt (Iface_Prim_Elmt);
5375 end loop;
5377 Next_Elmt (Iface_Elmt);
5378 end loop;
5379 end Check_Convention;
5381 -- Local variables
5383 Prim_Op : Entity_Id;
5384 Prim_Op_Elmt : Elmt_Id;
5386 -- Start of processing for Check_Conventions
5388 begin
5389 if not Has_Interfaces (Typ) then
5390 return;
5391 end if;
5393 Collect_Interfaces (Typ, Ifaces_List);
5395 -- The algorithm checks every overriding dispatching operation against
5396 -- all the corresponding overridden dispatching operations, detecting
5397 -- differences in conventions.
5399 Prim_Op_Elmt := First_Elmt (Primitive_Operations (Typ));
5400 while Present (Prim_Op_Elmt) loop
5401 Prim_Op := Node (Prim_Op_Elmt);
5403 -- A small optimization: skip the predefined dispatching operations
5404 -- since they always have the same convention.
5406 if not Is_Predefined_Dispatching_Operation (Prim_Op) then
5407 Check_Convention (Prim_Op);
5408 end if;
5410 Next_Elmt (Prim_Op_Elmt);
5411 end loop;
5412 end Check_Conventions;
5414 ------------------------------
5415 -- Check_Delayed_Subprogram --
5416 ------------------------------
5418 procedure Check_Delayed_Subprogram (Designator : Entity_Id) is
5419 F : Entity_Id;
5421 procedure Possible_Freeze (T : Entity_Id);
5422 -- T is the type of either a formal parameter or of the return type.
5423 -- If T is not yet frozen and needs a delayed freeze, then the
5424 -- subprogram itself must be delayed. If T is the limited view of an
5425 -- incomplete type the subprogram must be frozen as well, because
5426 -- T may depend on local types that have not been frozen yet.
5428 ---------------------
5429 -- Possible_Freeze --
5430 ---------------------
5432 procedure Possible_Freeze (T : Entity_Id) is
5433 begin
5434 if Has_Delayed_Freeze (T) and then not Is_Frozen (T) then
5435 Set_Has_Delayed_Freeze (Designator);
5437 elsif Is_Access_Type (T)
5438 and then Has_Delayed_Freeze (Designated_Type (T))
5439 and then not Is_Frozen (Designated_Type (T))
5440 then
5441 Set_Has_Delayed_Freeze (Designator);
5443 elsif Ekind (T) = E_Incomplete_Type
5444 and then From_Limited_With (T)
5445 then
5446 Set_Has_Delayed_Freeze (Designator);
5448 -- AI05-0151: In Ada 2012, Incomplete types can appear in the profile
5449 -- of a subprogram or entry declaration.
5451 elsif Ekind (T) = E_Incomplete_Type
5452 and then Ada_Version >= Ada_2012
5453 then
5454 Set_Has_Delayed_Freeze (Designator);
5455 end if;
5457 end Possible_Freeze;
5459 -- Start of processing for Check_Delayed_Subprogram
5461 begin
5462 -- All subprograms, including abstract subprograms, may need a freeze
5463 -- node if some formal type or the return type needs one.
5465 Possible_Freeze (Etype (Designator));
5466 Possible_Freeze (Base_Type (Etype (Designator))); -- needed ???
5468 -- Need delayed freeze if any of the formal types themselves need
5469 -- a delayed freeze and are not yet frozen.
5471 F := First_Formal (Designator);
5472 while Present (F) loop
5473 Possible_Freeze (Etype (F));
5474 Possible_Freeze (Base_Type (Etype (F))); -- needed ???
5475 Next_Formal (F);
5476 end loop;
5478 -- Mark functions that return by reference. Note that it cannot be
5479 -- done for delayed_freeze subprograms because the underlying
5480 -- returned type may not be known yet (for private types)
5482 if not Has_Delayed_Freeze (Designator) and then Expander_Active then
5483 declare
5484 Typ : constant Entity_Id := Etype (Designator);
5485 Utyp : constant Entity_Id := Underlying_Type (Typ);
5486 begin
5487 if Is_Limited_View (Typ) then
5488 Set_Returns_By_Ref (Designator);
5489 elsif Present (Utyp) and then CW_Or_Has_Controlled_Part (Utyp) then
5490 Set_Returns_By_Ref (Designator);
5491 end if;
5492 end;
5493 end if;
5494 end Check_Delayed_Subprogram;
5496 ------------------------------------
5497 -- Check_Discriminant_Conformance --
5498 ------------------------------------
5500 procedure Check_Discriminant_Conformance
5501 (N : Node_Id;
5502 Prev : Entity_Id;
5503 Prev_Loc : Node_Id)
5505 Old_Discr : Entity_Id := First_Discriminant (Prev);
5506 New_Discr : Node_Id := First (Discriminant_Specifications (N));
5507 New_Discr_Id : Entity_Id;
5508 New_Discr_Type : Entity_Id;
5510 procedure Conformance_Error (Msg : String; N : Node_Id);
5511 -- Post error message for conformance error on given node. Two messages
5512 -- are output. The first points to the previous declaration with a
5513 -- general "no conformance" message. The second is the detailed reason,
5514 -- supplied as Msg. The parameter N provide information for a possible
5515 -- & insertion in the message.
5517 -----------------------
5518 -- Conformance_Error --
5519 -----------------------
5521 procedure Conformance_Error (Msg : String; N : Node_Id) is
5522 begin
5523 Error_Msg_Sloc := Sloc (Prev_Loc);
5524 Error_Msg_N -- CODEFIX
5525 ("not fully conformant with declaration#!", N);
5526 Error_Msg_NE (Msg, N, N);
5527 end Conformance_Error;
5529 -- Start of processing for Check_Discriminant_Conformance
5531 begin
5532 while Present (Old_Discr) and then Present (New_Discr) loop
5533 New_Discr_Id := Defining_Identifier (New_Discr);
5535 -- The subtype mark of the discriminant on the full type has not
5536 -- been analyzed so we do it here. For an access discriminant a new
5537 -- type is created.
5539 if Nkind (Discriminant_Type (New_Discr)) = N_Access_Definition then
5540 New_Discr_Type :=
5541 Access_Definition (N, Discriminant_Type (New_Discr));
5543 else
5544 Analyze (Discriminant_Type (New_Discr));
5545 New_Discr_Type := Etype (Discriminant_Type (New_Discr));
5547 -- Ada 2005: if the discriminant definition carries a null
5548 -- exclusion, create an itype to check properly for consistency
5549 -- with partial declaration.
5551 if Is_Access_Type (New_Discr_Type)
5552 and then Null_Exclusion_Present (New_Discr)
5553 then
5554 New_Discr_Type :=
5555 Create_Null_Excluding_Itype
5556 (T => New_Discr_Type,
5557 Related_Nod => New_Discr,
5558 Scope_Id => Current_Scope);
5559 end if;
5560 end if;
5562 if not Conforming_Types
5563 (Etype (Old_Discr), New_Discr_Type, Fully_Conformant)
5564 then
5565 Conformance_Error ("type of & does not match!", New_Discr_Id);
5566 return;
5567 else
5568 -- Treat the new discriminant as an occurrence of the old one,
5569 -- for navigation purposes, and fill in some semantic
5570 -- information, for completeness.
5572 Generate_Reference (Old_Discr, New_Discr_Id, 'r');
5573 Set_Etype (New_Discr_Id, Etype (Old_Discr));
5574 Set_Scope (New_Discr_Id, Scope (Old_Discr));
5575 end if;
5577 -- Names must match
5579 if Chars (Old_Discr) /= Chars (Defining_Identifier (New_Discr)) then
5580 Conformance_Error ("name & does not match!", New_Discr_Id);
5581 return;
5582 end if;
5584 -- Default expressions must match
5586 declare
5587 NewD : constant Boolean :=
5588 Present (Expression (New_Discr));
5589 OldD : constant Boolean :=
5590 Present (Expression (Parent (Old_Discr)));
5592 begin
5593 if NewD or OldD then
5595 -- The old default value has been analyzed and expanded,
5596 -- because the current full declaration will have frozen
5597 -- everything before. The new default values have not been
5598 -- expanded, so expand now to check conformance.
5600 if NewD then
5601 Preanalyze_Spec_Expression
5602 (Expression (New_Discr), New_Discr_Type);
5603 end if;
5605 if not (NewD and OldD)
5606 or else not Fully_Conformant_Expressions
5607 (Expression (Parent (Old_Discr)),
5608 Expression (New_Discr))
5610 then
5611 Conformance_Error
5612 ("default expression for & does not match!",
5613 New_Discr_Id);
5614 return;
5615 end if;
5616 end if;
5617 end;
5619 -- In Ada 83 case, grouping must match: (A,B : X) /= (A : X; B : X)
5621 if Ada_Version = Ada_83 then
5622 declare
5623 Old_Disc : constant Node_Id := Declaration_Node (Old_Discr);
5625 begin
5626 -- Grouping (use of comma in param lists) must be the same
5627 -- This is where we catch a misconformance like:
5629 -- A, B : Integer
5630 -- A : Integer; B : Integer
5632 -- which are represented identically in the tree except
5633 -- for the setting of the flags More_Ids and Prev_Ids.
5635 if More_Ids (Old_Disc) /= More_Ids (New_Discr)
5636 or else Prev_Ids (Old_Disc) /= Prev_Ids (New_Discr)
5637 then
5638 Conformance_Error
5639 ("grouping of & does not match!", New_Discr_Id);
5640 return;
5641 end if;
5642 end;
5643 end if;
5645 Next_Discriminant (Old_Discr);
5646 Next (New_Discr);
5647 end loop;
5649 if Present (Old_Discr) then
5650 Conformance_Error ("too few discriminants!", Defining_Identifier (N));
5651 return;
5653 elsif Present (New_Discr) then
5654 Conformance_Error
5655 ("too many discriminants!", Defining_Identifier (New_Discr));
5656 return;
5657 end if;
5658 end Check_Discriminant_Conformance;
5660 ----------------------------
5661 -- Check_Fully_Conformant --
5662 ----------------------------
5664 procedure Check_Fully_Conformant
5665 (New_Id : Entity_Id;
5666 Old_Id : Entity_Id;
5667 Err_Loc : Node_Id := Empty)
5669 Result : Boolean;
5670 pragma Warnings (Off, Result);
5671 begin
5672 Check_Conformance
5673 (New_Id, Old_Id, Fully_Conformant, True, Result, Err_Loc);
5674 end Check_Fully_Conformant;
5676 ---------------------------
5677 -- Check_Mode_Conformant --
5678 ---------------------------
5680 procedure Check_Mode_Conformant
5681 (New_Id : Entity_Id;
5682 Old_Id : Entity_Id;
5683 Err_Loc : Node_Id := Empty;
5684 Get_Inst : Boolean := False)
5686 Result : Boolean;
5687 pragma Warnings (Off, Result);
5688 begin
5689 Check_Conformance
5690 (New_Id, Old_Id, Mode_Conformant, True, Result, Err_Loc, Get_Inst);
5691 end Check_Mode_Conformant;
5693 --------------------------------
5694 -- Check_Overriding_Indicator --
5695 --------------------------------
5697 procedure Check_Overriding_Indicator
5698 (Subp : Entity_Id;
5699 Overridden_Subp : Entity_Id;
5700 Is_Primitive : Boolean)
5702 Decl : Node_Id;
5703 Spec : Node_Id;
5705 begin
5706 -- No overriding indicator for literals
5708 if Ekind (Subp) = E_Enumeration_Literal then
5709 return;
5711 elsif Ekind (Subp) = E_Entry then
5712 Decl := Parent (Subp);
5714 -- No point in analyzing a malformed operator
5716 elsif Nkind (Subp) = N_Defining_Operator_Symbol
5717 and then Error_Posted (Subp)
5718 then
5719 return;
5721 else
5722 Decl := Unit_Declaration_Node (Subp);
5723 end if;
5725 if Nkind_In (Decl, N_Subprogram_Body,
5726 N_Subprogram_Body_Stub,
5727 N_Subprogram_Declaration,
5728 N_Abstract_Subprogram_Declaration,
5729 N_Subprogram_Renaming_Declaration)
5730 then
5731 Spec := Specification (Decl);
5733 elsif Nkind (Decl) = N_Entry_Declaration then
5734 Spec := Decl;
5736 else
5737 return;
5738 end if;
5740 -- The overriding operation is type conformant with the overridden one,
5741 -- but the names of the formals are not required to match. If the names
5742 -- appear permuted in the overriding operation, this is a possible
5743 -- source of confusion that is worth diagnosing. Controlling formals
5744 -- often carry names that reflect the type, and it is not worthwhile
5745 -- requiring that their names match.
5747 if Present (Overridden_Subp)
5748 and then Nkind (Subp) /= N_Defining_Operator_Symbol
5749 then
5750 declare
5751 Form1 : Entity_Id;
5752 Form2 : Entity_Id;
5754 begin
5755 Form1 := First_Formal (Subp);
5756 Form2 := First_Formal (Overridden_Subp);
5758 -- If the overriding operation is a synchronized operation, skip
5759 -- the first parameter of the overridden operation, which is
5760 -- implicit in the new one. If the operation is declared in the
5761 -- body it is not primitive and all formals must match.
5763 if Is_Concurrent_Type (Scope (Subp))
5764 and then Is_Tagged_Type (Scope (Subp))
5765 and then not Has_Completion (Scope (Subp))
5766 then
5767 Form2 := Next_Formal (Form2);
5768 end if;
5770 if Present (Form1) then
5771 Form1 := Next_Formal (Form1);
5772 Form2 := Next_Formal (Form2);
5773 end if;
5775 while Present (Form1) loop
5776 if not Is_Controlling_Formal (Form1)
5777 and then Present (Next_Formal (Form2))
5778 and then Chars (Form1) = Chars (Next_Formal (Form2))
5779 then
5780 Error_Msg_Node_2 := Alias (Overridden_Subp);
5781 Error_Msg_Sloc := Sloc (Error_Msg_Node_2);
5782 Error_Msg_NE
5783 ("& does not match corresponding formal of&#",
5784 Form1, Form1);
5785 exit;
5786 end if;
5788 Next_Formal (Form1);
5789 Next_Formal (Form2);
5790 end loop;
5791 end;
5792 end if;
5794 -- If there is an overridden subprogram, then check that there is no
5795 -- "not overriding" indicator, and mark the subprogram as overriding.
5796 -- This is not done if the overridden subprogram is marked as hidden,
5797 -- which can occur for the case of inherited controlled operations
5798 -- (see Derive_Subprogram), unless the inherited subprogram's parent
5799 -- subprogram is not itself hidden. (Note: This condition could probably
5800 -- be simplified, leaving out the testing for the specific controlled
5801 -- cases, but it seems safer and clearer this way, and echoes similar
5802 -- special-case tests of this kind in other places.)
5804 if Present (Overridden_Subp)
5805 and then (not Is_Hidden (Overridden_Subp)
5806 or else
5807 (Nam_In (Chars (Overridden_Subp), Name_Initialize,
5808 Name_Adjust,
5809 Name_Finalize)
5810 and then Present (Alias (Overridden_Subp))
5811 and then not Is_Hidden (Alias (Overridden_Subp))))
5812 then
5813 if Must_Not_Override (Spec) then
5814 Error_Msg_Sloc := Sloc (Overridden_Subp);
5816 if Ekind (Subp) = E_Entry then
5817 Error_Msg_NE
5818 ("entry & overrides inherited operation #", Spec, Subp);
5819 else
5820 Error_Msg_NE
5821 ("subprogram & overrides inherited operation #", Spec, Subp);
5822 end if;
5824 -- Special-case to fix a GNAT oddity: Limited_Controlled is declared
5825 -- as an extension of Root_Controlled, and thus has a useless Adjust
5826 -- operation. This operation should not be inherited by other limited
5827 -- controlled types. An explicit Adjust for them is not overriding.
5829 elsif Must_Override (Spec)
5830 and then Chars (Overridden_Subp) = Name_Adjust
5831 and then Is_Limited_Type (Etype (First_Formal (Subp)))
5832 and then Present (Alias (Overridden_Subp))
5833 and then
5834 Is_Predefined_File_Name
5835 (Unit_File_Name (Get_Source_Unit (Alias (Overridden_Subp))))
5836 then
5837 Error_Msg_NE ("subprogram & is not overriding", Spec, Subp);
5839 elsif Is_Subprogram (Subp) then
5840 if Is_Init_Proc (Subp) then
5841 null;
5843 elsif No (Overridden_Operation (Subp)) then
5845 -- For entities generated by Derive_Subprograms the overridden
5846 -- operation is the inherited primitive (which is available
5847 -- through the attribute alias)
5849 if (Is_Dispatching_Operation (Subp)
5850 or else Is_Dispatching_Operation (Overridden_Subp))
5851 and then not Comes_From_Source (Overridden_Subp)
5852 and then Find_Dispatching_Type (Overridden_Subp) =
5853 Find_Dispatching_Type (Subp)
5854 and then Present (Alias (Overridden_Subp))
5855 and then Comes_From_Source (Alias (Overridden_Subp))
5856 then
5857 Set_Overridden_Operation (Subp, Alias (Overridden_Subp));
5858 Inherit_Subprogram_Contract (Subp, Alias (Overridden_Subp));
5860 else
5861 Set_Overridden_Operation (Subp, Overridden_Subp);
5862 Inherit_Subprogram_Contract (Subp, Overridden_Subp);
5863 end if;
5864 end if;
5865 end if;
5867 -- If primitive flag is set or this is a protected operation, then
5868 -- the operation is overriding at the point of its declaration, so
5869 -- warn if necessary. Otherwise it may have been declared before the
5870 -- operation it overrides and no check is required.
5872 if Style_Check
5873 and then not Must_Override (Spec)
5874 and then (Is_Primitive
5875 or else Ekind (Scope (Subp)) = E_Protected_Type)
5876 then
5877 Style.Missing_Overriding (Decl, Subp);
5878 end if;
5880 -- If Subp is an operator, it may override a predefined operation, if
5881 -- it is defined in the same scope as the type to which it applies.
5882 -- In that case Overridden_Subp is empty because of our implicit
5883 -- representation for predefined operators. We have to check whether the
5884 -- signature of Subp matches that of a predefined operator. Note that
5885 -- first argument provides the name of the operator, and the second
5886 -- argument the signature that may match that of a standard operation.
5887 -- If the indicator is overriding, then the operator must match a
5888 -- predefined signature, because we know already that there is no
5889 -- explicit overridden operation.
5891 elsif Nkind (Subp) = N_Defining_Operator_Symbol then
5892 if Must_Not_Override (Spec) then
5894 -- If this is not a primitive or a protected subprogram, then
5895 -- "not overriding" is illegal.
5897 if not Is_Primitive
5898 and then Ekind (Scope (Subp)) /= E_Protected_Type
5899 then
5900 Error_Msg_N ("overriding indicator only allowed "
5901 & "if subprogram is primitive", Subp);
5903 elsif Can_Override_Operator (Subp) then
5904 Error_Msg_NE
5905 ("subprogram& overrides predefined operator ", Spec, Subp);
5906 end if;
5908 elsif Must_Override (Spec) then
5909 if No (Overridden_Operation (Subp))
5910 and then not Can_Override_Operator (Subp)
5911 then
5912 Error_Msg_NE ("subprogram & is not overriding", Spec, Subp);
5913 end if;
5915 elsif not Error_Posted (Subp)
5916 and then Style_Check
5917 and then Can_Override_Operator (Subp)
5918 and then
5919 not Is_Predefined_File_Name
5920 (Unit_File_Name (Get_Source_Unit (Subp)))
5921 then
5922 -- If style checks are enabled, indicate that the indicator is
5923 -- missing. However, at the point of declaration, the type of
5924 -- which this is a primitive operation may be private, in which
5925 -- case the indicator would be premature.
5927 if Has_Private_Declaration (Etype (Subp))
5928 or else Has_Private_Declaration (Etype (First_Formal (Subp)))
5929 then
5930 null;
5931 else
5932 Style.Missing_Overriding (Decl, Subp);
5933 end if;
5934 end if;
5936 elsif Must_Override (Spec) then
5937 if Ekind (Subp) = E_Entry then
5938 Error_Msg_NE ("entry & is not overriding", Spec, Subp);
5939 else
5940 Error_Msg_NE ("subprogram & is not overriding", Spec, Subp);
5941 end if;
5943 -- If the operation is marked "not overriding" and it's not primitive
5944 -- then an error is issued, unless this is an operation of a task or
5945 -- protected type (RM05-8.3.1(3/2-4/2)). Error cases where "overriding"
5946 -- has been specified have already been checked above.
5948 elsif Must_Not_Override (Spec)
5949 and then not Is_Primitive
5950 and then Ekind (Subp) /= E_Entry
5951 and then Ekind (Scope (Subp)) /= E_Protected_Type
5952 then
5953 Error_Msg_N
5954 ("overriding indicator only allowed if subprogram is primitive",
5955 Subp);
5956 return;
5957 end if;
5958 end Check_Overriding_Indicator;
5960 -------------------
5961 -- Check_Returns --
5962 -------------------
5964 -- Note: this procedure needs to know far too much about how the expander
5965 -- messes with exceptions. The use of the flag Exception_Junk and the
5966 -- incorporation of knowledge of Exp_Ch11.Expand_Local_Exception_Handlers
5967 -- works, but is not very clean. It would be better if the expansion
5968 -- routines would leave Original_Node working nicely, and we could use
5969 -- Original_Node here to ignore all the peculiar expander messing ???
5971 procedure Check_Returns
5972 (HSS : Node_Id;
5973 Mode : Character;
5974 Err : out Boolean;
5975 Proc : Entity_Id := Empty)
5977 Handler : Node_Id;
5979 procedure Check_Statement_Sequence (L : List_Id);
5980 -- Internal recursive procedure to check a list of statements for proper
5981 -- termination by a return statement (or a transfer of control or a
5982 -- compound statement that is itself internally properly terminated).
5984 ------------------------------
5985 -- Check_Statement_Sequence --
5986 ------------------------------
5988 procedure Check_Statement_Sequence (L : List_Id) is
5989 Last_Stm : Node_Id;
5990 Stm : Node_Id;
5991 Kind : Node_Kind;
5993 function Assert_False return Boolean;
5994 -- Returns True if Last_Stm is a pragma Assert (False) that has been
5995 -- rewritten as a null statement when assertions are off. The assert
5996 -- is not active, but it is still enough to kill the warning.
5998 ------------------
5999 -- Assert_False --
6000 ------------------
6002 function Assert_False return Boolean is
6003 Orig : constant Node_Id := Original_Node (Last_Stm);
6005 begin
6006 if Nkind (Orig) = N_Pragma
6007 and then Pragma_Name (Orig) = Name_Assert
6008 and then not Error_Posted (Orig)
6009 then
6010 declare
6011 Arg : constant Node_Id :=
6012 First (Pragma_Argument_Associations (Orig));
6013 Exp : constant Node_Id := Expression (Arg);
6014 begin
6015 return Nkind (Exp) = N_Identifier
6016 and then Chars (Exp) = Name_False;
6017 end;
6019 else
6020 return False;
6021 end if;
6022 end Assert_False;
6024 -- Local variables
6026 Raise_Exception_Call : Boolean;
6027 -- Set True if statement sequence terminated by Raise_Exception call
6028 -- or a Reraise_Occurrence call.
6030 -- Start of processing for Check_Statement_Sequence
6032 begin
6033 Raise_Exception_Call := False;
6035 -- Get last real statement
6037 Last_Stm := Last (L);
6039 -- Deal with digging out exception handler statement sequences that
6040 -- have been transformed by the local raise to goto optimization.
6041 -- See Exp_Ch11.Expand_Local_Exception_Handlers for details. If this
6042 -- optimization has occurred, we are looking at something like:
6044 -- begin
6045 -- original stmts in block
6047 -- exception \
6048 -- when excep1 => |
6049 -- goto L1; | omitted if No_Exception_Propagation
6050 -- when excep2 => |
6051 -- goto L2; /
6052 -- end;
6054 -- goto L3; -- skip handler when exception not raised
6056 -- <<L1>> -- target label for local exception
6057 -- begin
6058 -- estmts1
6059 -- end;
6061 -- goto L3;
6063 -- <<L2>>
6064 -- begin
6065 -- estmts2
6066 -- end;
6068 -- <<L3>>
6070 -- and what we have to do is to dig out the estmts1 and estmts2
6071 -- sequences (which were the original sequences of statements in
6072 -- the exception handlers) and check them.
6074 if Nkind (Last_Stm) = N_Label and then Exception_Junk (Last_Stm) then
6075 Stm := Last_Stm;
6076 loop
6077 Prev (Stm);
6078 exit when No (Stm);
6079 exit when Nkind (Stm) /= N_Block_Statement;
6080 exit when not Exception_Junk (Stm);
6081 Prev (Stm);
6082 exit when No (Stm);
6083 exit when Nkind (Stm) /= N_Label;
6084 exit when not Exception_Junk (Stm);
6085 Check_Statement_Sequence
6086 (Statements (Handled_Statement_Sequence (Next (Stm))));
6088 Prev (Stm);
6089 Last_Stm := Stm;
6090 exit when No (Stm);
6091 exit when Nkind (Stm) /= N_Goto_Statement;
6092 exit when not Exception_Junk (Stm);
6093 end loop;
6094 end if;
6096 -- Don't count pragmas
6098 while Nkind (Last_Stm) = N_Pragma
6100 -- Don't count call to SS_Release (can happen after Raise_Exception)
6102 or else
6103 (Nkind (Last_Stm) = N_Procedure_Call_Statement
6104 and then
6105 Nkind (Name (Last_Stm)) = N_Identifier
6106 and then
6107 Is_RTE (Entity (Name (Last_Stm)), RE_SS_Release))
6109 -- Don't count exception junk
6111 or else
6112 (Nkind_In (Last_Stm, N_Goto_Statement,
6113 N_Label,
6114 N_Object_Declaration)
6115 and then Exception_Junk (Last_Stm))
6116 or else Nkind (Last_Stm) in N_Push_xxx_Label
6117 or else Nkind (Last_Stm) in N_Pop_xxx_Label
6119 -- Inserted code, such as finalization calls, is irrelevant: we only
6120 -- need to check original source.
6122 or else Is_Rewrite_Insertion (Last_Stm)
6123 loop
6124 Prev (Last_Stm);
6125 end loop;
6127 -- Here we have the "real" last statement
6129 Kind := Nkind (Last_Stm);
6131 -- Transfer of control, OK. Note that in the No_Return procedure
6132 -- case, we already diagnosed any explicit return statements, so
6133 -- we can treat them as OK in this context.
6135 if Is_Transfer (Last_Stm) then
6136 return;
6138 -- Check cases of explicit non-indirect procedure calls
6140 elsif Kind = N_Procedure_Call_Statement
6141 and then Is_Entity_Name (Name (Last_Stm))
6142 then
6143 -- Check call to Raise_Exception procedure which is treated
6144 -- specially, as is a call to Reraise_Occurrence.
6146 -- We suppress the warning in these cases since it is likely that
6147 -- the programmer really does not expect to deal with the case
6148 -- of Null_Occurrence, and thus would find a warning about a
6149 -- missing return curious, and raising Program_Error does not
6150 -- seem such a bad behavior if this does occur.
6152 -- Note that in the Ada 2005 case for Raise_Exception, the actual
6153 -- behavior will be to raise Constraint_Error (see AI-329).
6155 if Is_RTE (Entity (Name (Last_Stm)), RE_Raise_Exception)
6156 or else
6157 Is_RTE (Entity (Name (Last_Stm)), RE_Reraise_Occurrence)
6158 then
6159 Raise_Exception_Call := True;
6161 -- For Raise_Exception call, test first argument, if it is
6162 -- an attribute reference for a 'Identity call, then we know
6163 -- that the call cannot possibly return.
6165 declare
6166 Arg : constant Node_Id :=
6167 Original_Node (First_Actual (Last_Stm));
6168 begin
6169 if Nkind (Arg) = N_Attribute_Reference
6170 and then Attribute_Name (Arg) = Name_Identity
6171 then
6172 return;
6173 end if;
6174 end;
6175 end if;
6177 -- If statement, need to look inside if there is an else and check
6178 -- each constituent statement sequence for proper termination.
6180 elsif Kind = N_If_Statement
6181 and then Present (Else_Statements (Last_Stm))
6182 then
6183 Check_Statement_Sequence (Then_Statements (Last_Stm));
6184 Check_Statement_Sequence (Else_Statements (Last_Stm));
6186 if Present (Elsif_Parts (Last_Stm)) then
6187 declare
6188 Elsif_Part : Node_Id := First (Elsif_Parts (Last_Stm));
6190 begin
6191 while Present (Elsif_Part) loop
6192 Check_Statement_Sequence (Then_Statements (Elsif_Part));
6193 Next (Elsif_Part);
6194 end loop;
6195 end;
6196 end if;
6198 return;
6200 -- Case statement, check each case for proper termination
6202 elsif Kind = N_Case_Statement then
6203 declare
6204 Case_Alt : Node_Id;
6205 begin
6206 Case_Alt := First_Non_Pragma (Alternatives (Last_Stm));
6207 while Present (Case_Alt) loop
6208 Check_Statement_Sequence (Statements (Case_Alt));
6209 Next_Non_Pragma (Case_Alt);
6210 end loop;
6211 end;
6213 return;
6215 -- Block statement, check its handled sequence of statements
6217 elsif Kind = N_Block_Statement then
6218 declare
6219 Err1 : Boolean;
6221 begin
6222 Check_Returns
6223 (Handled_Statement_Sequence (Last_Stm), Mode, Err1);
6225 if Err1 then
6226 Err := True;
6227 end if;
6229 return;
6230 end;
6232 -- Loop statement. If there is an iteration scheme, we can definitely
6233 -- fall out of the loop. Similarly if there is an exit statement, we
6234 -- can fall out. In either case we need a following return.
6236 elsif Kind = N_Loop_Statement then
6237 if Present (Iteration_Scheme (Last_Stm))
6238 or else Has_Exit (Entity (Identifier (Last_Stm)))
6239 then
6240 null;
6242 -- A loop with no exit statement or iteration scheme is either
6243 -- an infinite loop, or it has some other exit (raise/return).
6244 -- In either case, no warning is required.
6246 else
6247 return;
6248 end if;
6250 -- Timed entry call, check entry call and delay alternatives
6252 -- Note: in expanded code, the timed entry call has been converted
6253 -- to a set of expanded statements on which the check will work
6254 -- correctly in any case.
6256 elsif Kind = N_Timed_Entry_Call then
6257 declare
6258 ECA : constant Node_Id := Entry_Call_Alternative (Last_Stm);
6259 DCA : constant Node_Id := Delay_Alternative (Last_Stm);
6261 begin
6262 -- If statement sequence of entry call alternative is missing,
6263 -- then we can definitely fall through, and we post the error
6264 -- message on the entry call alternative itself.
6266 if No (Statements (ECA)) then
6267 Last_Stm := ECA;
6269 -- If statement sequence of delay alternative is missing, then
6270 -- we can definitely fall through, and we post the error
6271 -- message on the delay alternative itself.
6273 -- Note: if both ECA and DCA are missing the return, then we
6274 -- post only one message, should be enough to fix the bugs.
6275 -- If not we will get a message next time on the DCA when the
6276 -- ECA is fixed.
6278 elsif No (Statements (DCA)) then
6279 Last_Stm := DCA;
6281 -- Else check both statement sequences
6283 else
6284 Check_Statement_Sequence (Statements (ECA));
6285 Check_Statement_Sequence (Statements (DCA));
6286 return;
6287 end if;
6288 end;
6290 -- Conditional entry call, check entry call and else part
6292 -- Note: in expanded code, the conditional entry call has been
6293 -- converted to a set of expanded statements on which the check
6294 -- will work correctly in any case.
6296 elsif Kind = N_Conditional_Entry_Call then
6297 declare
6298 ECA : constant Node_Id := Entry_Call_Alternative (Last_Stm);
6300 begin
6301 -- If statement sequence of entry call alternative is missing,
6302 -- then we can definitely fall through, and we post the error
6303 -- message on the entry call alternative itself.
6305 if No (Statements (ECA)) then
6306 Last_Stm := ECA;
6308 -- Else check statement sequence and else part
6310 else
6311 Check_Statement_Sequence (Statements (ECA));
6312 Check_Statement_Sequence (Else_Statements (Last_Stm));
6313 return;
6314 end if;
6315 end;
6316 end if;
6318 -- If we fall through, issue appropriate message
6320 if Mode = 'F' then
6322 -- Kill warning if last statement is a raise exception call,
6323 -- or a pragma Assert (False). Note that with assertions enabled,
6324 -- such a pragma has been converted into a raise exception call
6325 -- already, so the Assert_False is for the assertions off case.
6327 if not Raise_Exception_Call and then not Assert_False then
6329 -- In GNATprove mode, it is an error to have a missing return
6331 Error_Msg_Warn := SPARK_Mode /= On;
6333 -- Issue error message or warning
6335 Error_Msg_N
6336 ("RETURN statement missing following this statement<<!",
6337 Last_Stm);
6338 Error_Msg_N
6339 ("\Program_Error ]<<!", Last_Stm);
6340 end if;
6342 -- Note: we set Err even though we have not issued a warning
6343 -- because we still have a case of a missing return. This is
6344 -- an extremely marginal case, probably will never be noticed
6345 -- but we might as well get it right.
6347 Err := True;
6349 -- Otherwise we have the case of a procedure marked No_Return
6351 else
6352 if not Raise_Exception_Call then
6353 if GNATprove_Mode then
6354 Error_Msg_N
6355 ("implied return after this statement "
6356 & "would have raised Program_Error", Last_Stm);
6357 else
6358 Error_Msg_N
6359 ("implied return after this statement "
6360 & "will raise Program_Error??", Last_Stm);
6361 end if;
6363 Error_Msg_Warn := SPARK_Mode /= On;
6364 Error_Msg_NE
6365 ("\procedure & is marked as No_Return<<!", Last_Stm, Proc);
6366 end if;
6368 declare
6369 RE : constant Node_Id :=
6370 Make_Raise_Program_Error (Sloc (Last_Stm),
6371 Reason => PE_Implicit_Return);
6372 begin
6373 Insert_After (Last_Stm, RE);
6374 Analyze (RE);
6375 end;
6376 end if;
6377 end Check_Statement_Sequence;
6379 -- Start of processing for Check_Returns
6381 begin
6382 Err := False;
6383 Check_Statement_Sequence (Statements (HSS));
6385 if Present (Exception_Handlers (HSS)) then
6386 Handler := First_Non_Pragma (Exception_Handlers (HSS));
6387 while Present (Handler) loop
6388 Check_Statement_Sequence (Statements (Handler));
6389 Next_Non_Pragma (Handler);
6390 end loop;
6391 end if;
6392 end Check_Returns;
6394 ----------------------------
6395 -- Check_Subprogram_Order --
6396 ----------------------------
6398 procedure Check_Subprogram_Order (N : Node_Id) is
6400 function Subprogram_Name_Greater (S1, S2 : String) return Boolean;
6401 -- This is used to check if S1 > S2 in the sense required by this test,
6402 -- for example nameab < namec, but name2 < name10.
6404 -----------------------------
6405 -- Subprogram_Name_Greater --
6406 -----------------------------
6408 function Subprogram_Name_Greater (S1, S2 : String) return Boolean is
6409 L1, L2 : Positive;
6410 N1, N2 : Natural;
6412 begin
6413 -- Deal with special case where names are identical except for a
6414 -- numerical suffix. These are handled specially, taking the numeric
6415 -- ordering from the suffix into account.
6417 L1 := S1'Last;
6418 while S1 (L1) in '0' .. '9' loop
6419 L1 := L1 - 1;
6420 end loop;
6422 L2 := S2'Last;
6423 while S2 (L2) in '0' .. '9' loop
6424 L2 := L2 - 1;
6425 end loop;
6427 -- If non-numeric parts non-equal, do straight compare
6429 if S1 (S1'First .. L1) /= S2 (S2'First .. L2) then
6430 return S1 > S2;
6432 -- If non-numeric parts equal, compare suffixed numeric parts. Note
6433 -- that a missing suffix is treated as numeric zero in this test.
6435 else
6436 N1 := 0;
6437 while L1 < S1'Last loop
6438 L1 := L1 + 1;
6439 N1 := N1 * 10 + Character'Pos (S1 (L1)) - Character'Pos ('0');
6440 end loop;
6442 N2 := 0;
6443 while L2 < S2'Last loop
6444 L2 := L2 + 1;
6445 N2 := N2 * 10 + Character'Pos (S2 (L2)) - Character'Pos ('0');
6446 end loop;
6448 return N1 > N2;
6449 end if;
6450 end Subprogram_Name_Greater;
6452 -- Start of processing for Check_Subprogram_Order
6454 begin
6455 -- Check body in alpha order if this is option
6457 if Style_Check
6458 and then Style_Check_Order_Subprograms
6459 and then Nkind (N) = N_Subprogram_Body
6460 and then Comes_From_Source (N)
6461 and then In_Extended_Main_Source_Unit (N)
6462 then
6463 declare
6464 LSN : String_Ptr
6465 renames Scope_Stack.Table
6466 (Scope_Stack.Last).Last_Subprogram_Name;
6468 Body_Id : constant Entity_Id :=
6469 Defining_Entity (Specification (N));
6471 begin
6472 Get_Decoded_Name_String (Chars (Body_Id));
6474 if LSN /= null then
6475 if Subprogram_Name_Greater
6476 (LSN.all, Name_Buffer (1 .. Name_Len))
6477 then
6478 Style.Subprogram_Not_In_Alpha_Order (Body_Id);
6479 end if;
6481 Free (LSN);
6482 end if;
6484 LSN := new String'(Name_Buffer (1 .. Name_Len));
6485 end;
6486 end if;
6487 end Check_Subprogram_Order;
6489 ------------------------------
6490 -- Check_Subtype_Conformant --
6491 ------------------------------
6493 procedure Check_Subtype_Conformant
6494 (New_Id : Entity_Id;
6495 Old_Id : Entity_Id;
6496 Err_Loc : Node_Id := Empty;
6497 Skip_Controlling_Formals : Boolean := False;
6498 Get_Inst : Boolean := False)
6500 Result : Boolean;
6501 pragma Warnings (Off, Result);
6502 begin
6503 Check_Conformance
6504 (New_Id, Old_Id, Subtype_Conformant, True, Result, Err_Loc,
6505 Skip_Controlling_Formals => Skip_Controlling_Formals,
6506 Get_Inst => Get_Inst);
6507 end Check_Subtype_Conformant;
6509 ---------------------------
6510 -- Check_Type_Conformant --
6511 ---------------------------
6513 procedure Check_Type_Conformant
6514 (New_Id : Entity_Id;
6515 Old_Id : Entity_Id;
6516 Err_Loc : Node_Id := Empty)
6518 Result : Boolean;
6519 pragma Warnings (Off, Result);
6520 begin
6521 Check_Conformance
6522 (New_Id, Old_Id, Type_Conformant, True, Result, Err_Loc);
6523 end Check_Type_Conformant;
6525 ---------------------------
6526 -- Can_Override_Operator --
6527 ---------------------------
6529 function Can_Override_Operator (Subp : Entity_Id) return Boolean is
6530 Typ : Entity_Id;
6532 begin
6533 if Nkind (Subp) /= N_Defining_Operator_Symbol then
6534 return False;
6536 else
6537 Typ := Base_Type (Etype (First_Formal (Subp)));
6539 -- Check explicitly that the operation is a primitive of the type
6541 return Operator_Matches_Spec (Subp, Subp)
6542 and then not Is_Generic_Type (Typ)
6543 and then Scope (Subp) = Scope (Typ)
6544 and then not Is_Class_Wide_Type (Typ);
6545 end if;
6546 end Can_Override_Operator;
6548 ----------------------
6549 -- Conforming_Types --
6550 ----------------------
6552 function Conforming_Types
6553 (T1 : Entity_Id;
6554 T2 : Entity_Id;
6555 Ctype : Conformance_Type;
6556 Get_Inst : Boolean := False) return Boolean
6558 Type_1 : Entity_Id := T1;
6559 Type_2 : Entity_Id := T2;
6560 Are_Anonymous_Access_To_Subprogram_Types : Boolean := False;
6562 function Base_Types_Match (T1, T2 : Entity_Id) return Boolean;
6563 -- If neither T1 nor T2 are generic actual types, or if they are in
6564 -- different scopes (e.g. parent and child instances), then verify that
6565 -- the base types are equal. Otherwise T1 and T2 must be on the same
6566 -- subtype chain. The whole purpose of this procedure is to prevent
6567 -- spurious ambiguities in an instantiation that may arise if two
6568 -- distinct generic types are instantiated with the same actual.
6570 function Find_Designated_Type (T : Entity_Id) return Entity_Id;
6571 -- An access parameter can designate an incomplete type. If the
6572 -- incomplete type is the limited view of a type from a limited_
6573 -- with_clause, check whether the non-limited view is available. If
6574 -- it is a (non-limited) incomplete type, get the full view.
6576 function Matches_Limited_With_View (T1, T2 : Entity_Id) return Boolean;
6577 -- Returns True if and only if either T1 denotes a limited view of T2
6578 -- or T2 denotes a limited view of T1. This can arise when the limited
6579 -- with view of a type is used in a subprogram declaration and the
6580 -- subprogram body is in the scope of a regular with clause for the
6581 -- same unit. In such a case, the two type entities can be considered
6582 -- identical for purposes of conformance checking.
6584 ----------------------
6585 -- Base_Types_Match --
6586 ----------------------
6588 function Base_Types_Match (T1, T2 : Entity_Id) return Boolean is
6589 BT1 : constant Entity_Id := Base_Type (T1);
6590 BT2 : constant Entity_Id := Base_Type (T2);
6592 begin
6593 if T1 = T2 then
6594 return True;
6596 elsif BT1 = BT2 then
6598 -- The following is too permissive. A more precise test should
6599 -- check that the generic actual is an ancestor subtype of the
6600 -- other ???.
6602 -- See code in Find_Corresponding_Spec that applies an additional
6603 -- filter to handle accidental amiguities in instances.
6605 return not Is_Generic_Actual_Type (T1)
6606 or else not Is_Generic_Actual_Type (T2)
6607 or else Scope (T1) /= Scope (T2);
6609 -- If T2 is a generic actual type it is declared as the subtype of
6610 -- the actual. If that actual is itself a subtype we need to use its
6611 -- own base type to check for compatibility.
6613 elsif Ekind (BT2) = Ekind (T2) and then BT1 = Base_Type (BT2) then
6614 return True;
6616 elsif Ekind (BT1) = Ekind (T1) and then BT2 = Base_Type (BT1) then
6617 return True;
6619 else
6620 return False;
6621 end if;
6622 end Base_Types_Match;
6624 --------------------------
6625 -- Find_Designated_Type --
6626 --------------------------
6628 function Find_Designated_Type (T : Entity_Id) return Entity_Id is
6629 Desig : Entity_Id;
6631 begin
6632 Desig := Directly_Designated_Type (T);
6634 if Ekind (Desig) = E_Incomplete_Type then
6636 -- If regular incomplete type, get full view if available
6638 if Present (Full_View (Desig)) then
6639 Desig := Full_View (Desig);
6641 -- If limited view of a type, get non-limited view if available,
6642 -- and check again for a regular incomplete type.
6644 elsif Present (Non_Limited_View (Desig)) then
6645 Desig := Get_Full_View (Non_Limited_View (Desig));
6646 end if;
6647 end if;
6649 return Desig;
6650 end Find_Designated_Type;
6652 -------------------------------
6653 -- Matches_Limited_With_View --
6654 -------------------------------
6656 function Matches_Limited_With_View (T1, T2 : Entity_Id) return Boolean is
6657 begin
6658 -- In some cases a type imported through a limited_with clause, and
6659 -- its nonlimited view are both visible, for example in an anonymous
6660 -- access-to-class-wide type in a formal, or when building the body
6661 -- for a subprogram renaming after the subprogram has been frozen.
6662 -- In these cases Both entities designate the same type. In addition,
6663 -- if one of them is an actual in an instance, it may be a subtype of
6664 -- the non-limited view of the other.
6666 if From_Limited_With (T1)
6667 and then (T2 = Available_View (T1)
6668 or else Is_Subtype_Of (T2, Available_View (T1)))
6669 then
6670 return True;
6672 elsif From_Limited_With (T2)
6673 and then (T1 = Available_View (T2)
6674 or else Is_Subtype_Of (T1, Available_View (T2)))
6675 then
6676 return True;
6678 elsif From_Limited_With (T1)
6679 and then From_Limited_With (T2)
6680 and then Available_View (T1) = Available_View (T2)
6681 then
6682 return True;
6684 else
6685 return False;
6686 end if;
6687 end Matches_Limited_With_View;
6689 -- Start of processing for Conforming_Types
6691 begin
6692 -- The context is an instance association for a formal access-to-
6693 -- subprogram type; the formal parameter types require mapping because
6694 -- they may denote other formal parameters of the generic unit.
6696 if Get_Inst then
6697 Type_1 := Get_Instance_Of (T1);
6698 Type_2 := Get_Instance_Of (T2);
6699 end if;
6701 -- If one of the types is a view of the other introduced by a limited
6702 -- with clause, treat these as conforming for all purposes.
6704 if Matches_Limited_With_View (T1, T2) then
6705 return True;
6707 elsif Base_Types_Match (Type_1, Type_2) then
6708 return Ctype <= Mode_Conformant
6709 or else Subtypes_Statically_Match (Type_1, Type_2);
6711 elsif Is_Incomplete_Or_Private_Type (Type_1)
6712 and then Present (Full_View (Type_1))
6713 and then Base_Types_Match (Full_View (Type_1), Type_2)
6714 then
6715 return Ctype <= Mode_Conformant
6716 or else Subtypes_Statically_Match (Full_View (Type_1), Type_2);
6718 elsif Ekind (Type_2) = E_Incomplete_Type
6719 and then Present (Full_View (Type_2))
6720 and then Base_Types_Match (Type_1, Full_View (Type_2))
6721 then
6722 return Ctype <= Mode_Conformant
6723 or else Subtypes_Statically_Match (Type_1, Full_View (Type_2));
6725 elsif Is_Private_Type (Type_2)
6726 and then In_Instance
6727 and then Present (Full_View (Type_2))
6728 and then Base_Types_Match (Type_1, Full_View (Type_2))
6729 then
6730 return Ctype <= Mode_Conformant
6731 or else Subtypes_Statically_Match (Type_1, Full_View (Type_2));
6732 end if;
6734 -- Ada 2005 (AI-254): Anonymous access-to-subprogram types must be
6735 -- treated recursively because they carry a signature. As far as
6736 -- conformance is concerned, convention plays no role, and either
6737 -- or both could be access to protected subprograms.
6739 Are_Anonymous_Access_To_Subprogram_Types :=
6740 Ekind_In (Type_1, E_Anonymous_Access_Subprogram_Type,
6741 E_Anonymous_Access_Protected_Subprogram_Type)
6742 and then
6743 Ekind_In (Type_2, E_Anonymous_Access_Subprogram_Type,
6744 E_Anonymous_Access_Protected_Subprogram_Type);
6746 -- Test anonymous access type case. For this case, static subtype
6747 -- matching is required for mode conformance (RM 6.3.1(15)). We check
6748 -- the base types because we may have built internal subtype entities
6749 -- to handle null-excluding types (see Process_Formals).
6751 if (Ekind (Base_Type (Type_1)) = E_Anonymous_Access_Type
6752 and then
6753 Ekind (Base_Type (Type_2)) = E_Anonymous_Access_Type)
6755 -- Ada 2005 (AI-254)
6757 or else Are_Anonymous_Access_To_Subprogram_Types
6758 then
6759 declare
6760 Desig_1 : Entity_Id;
6761 Desig_2 : Entity_Id;
6763 begin
6764 -- In Ada 2005, access constant indicators must match for
6765 -- subtype conformance.
6767 if Ada_Version >= Ada_2005
6768 and then Ctype >= Subtype_Conformant
6769 and then
6770 Is_Access_Constant (Type_1) /= Is_Access_Constant (Type_2)
6771 then
6772 return False;
6773 end if;
6775 Desig_1 := Find_Designated_Type (Type_1);
6776 Desig_2 := Find_Designated_Type (Type_2);
6778 -- If the context is an instance association for a formal
6779 -- access-to-subprogram type; formal access parameter designated
6780 -- types require mapping because they may denote other formal
6781 -- parameters of the generic unit.
6783 if Get_Inst then
6784 Desig_1 := Get_Instance_Of (Desig_1);
6785 Desig_2 := Get_Instance_Of (Desig_2);
6786 end if;
6788 -- It is possible for a Class_Wide_Type to be introduced for an
6789 -- incomplete type, in which case there is a separate class_ wide
6790 -- type for the full view. The types conform if their Etypes
6791 -- conform, i.e. one may be the full view of the other. This can
6792 -- only happen in the context of an access parameter, other uses
6793 -- of an incomplete Class_Wide_Type are illegal.
6795 if Is_Class_Wide_Type (Desig_1)
6796 and then
6797 Is_Class_Wide_Type (Desig_2)
6798 then
6799 return
6800 Conforming_Types
6801 (Etype (Base_Type (Desig_1)),
6802 Etype (Base_Type (Desig_2)), Ctype);
6804 elsif Are_Anonymous_Access_To_Subprogram_Types then
6805 if Ada_Version < Ada_2005 then
6806 return Ctype = Type_Conformant
6807 or else
6808 Subtypes_Statically_Match (Desig_1, Desig_2);
6810 -- We must check the conformance of the signatures themselves
6812 else
6813 declare
6814 Conformant : Boolean;
6815 begin
6816 Check_Conformance
6817 (Desig_1, Desig_2, Ctype, False, Conformant);
6818 return Conformant;
6819 end;
6820 end if;
6822 else
6823 return Base_Type (Desig_1) = Base_Type (Desig_2)
6824 and then (Ctype = Type_Conformant
6825 or else
6826 Subtypes_Statically_Match (Desig_1, Desig_2));
6827 end if;
6828 end;
6830 -- Otherwise definitely no match
6832 else
6833 if ((Ekind (Type_1) = E_Anonymous_Access_Type
6834 and then Is_Access_Type (Type_2))
6835 or else (Ekind (Type_2) = E_Anonymous_Access_Type
6836 and then Is_Access_Type (Type_1)))
6837 and then
6838 Conforming_Types
6839 (Designated_Type (Type_1), Designated_Type (Type_2), Ctype)
6840 then
6841 May_Hide_Profile := True;
6842 end if;
6844 return False;
6845 end if;
6846 end Conforming_Types;
6848 --------------------------
6849 -- Create_Extra_Formals --
6850 --------------------------
6852 procedure Create_Extra_Formals (E : Entity_Id) is
6853 Formal : Entity_Id;
6854 First_Extra : Entity_Id := Empty;
6855 Last_Extra : Entity_Id;
6856 Formal_Type : Entity_Id;
6857 P_Formal : Entity_Id := Empty;
6859 function Add_Extra_Formal
6860 (Assoc_Entity : Entity_Id;
6861 Typ : Entity_Id;
6862 Scope : Entity_Id;
6863 Suffix : String) return Entity_Id;
6864 -- Add an extra formal to the current list of formals and extra formals.
6865 -- The extra formal is added to the end of the list of extra formals,
6866 -- and also returned as the result. These formals are always of mode IN.
6867 -- The new formal has the type Typ, is declared in Scope, and its name
6868 -- is given by a concatenation of the name of Assoc_Entity and Suffix.
6869 -- The following suffixes are currently used. They should not be changed
6870 -- without coordinating with CodePeer, which makes use of these to
6871 -- provide better messages.
6873 -- O denotes the Constrained bit.
6874 -- L denotes the accessibility level.
6875 -- BIP_xxx denotes an extra formal for a build-in-place function. See
6876 -- the full list in exp_ch6.BIP_Formal_Kind.
6878 ----------------------
6879 -- Add_Extra_Formal --
6880 ----------------------
6882 function Add_Extra_Formal
6883 (Assoc_Entity : Entity_Id;
6884 Typ : Entity_Id;
6885 Scope : Entity_Id;
6886 Suffix : String) return Entity_Id
6888 EF : constant Entity_Id :=
6889 Make_Defining_Identifier (Sloc (Assoc_Entity),
6890 Chars => New_External_Name (Chars (Assoc_Entity),
6891 Suffix => Suffix));
6893 begin
6894 -- A little optimization. Never generate an extra formal for the
6895 -- _init operand of an initialization procedure, since it could
6896 -- never be used.
6898 if Chars (Formal) = Name_uInit then
6899 return Empty;
6900 end if;
6902 Set_Ekind (EF, E_In_Parameter);
6903 Set_Actual_Subtype (EF, Typ);
6904 Set_Etype (EF, Typ);
6905 Set_Scope (EF, Scope);
6906 Set_Mechanism (EF, Default_Mechanism);
6907 Set_Formal_Validity (EF);
6909 if No (First_Extra) then
6910 First_Extra := EF;
6911 Set_Extra_Formals (Scope, First_Extra);
6912 end if;
6914 if Present (Last_Extra) then
6915 Set_Extra_Formal (Last_Extra, EF);
6916 end if;
6918 Last_Extra := EF;
6920 return EF;
6921 end Add_Extra_Formal;
6923 -- Start of processing for Create_Extra_Formals
6925 begin
6926 -- We never generate extra formals if expansion is not active because we
6927 -- don't need them unless we are generating code.
6929 if not Expander_Active then
6930 return;
6931 end if;
6933 -- No need to generate extra formals in interface thunks whose target
6934 -- primitive has no extra formals.
6936 if Is_Thunk (E) and then No (Extra_Formals (Thunk_Entity (E))) then
6937 return;
6938 end if;
6940 -- If this is a derived subprogram then the subtypes of the parent
6941 -- subprogram's formal parameters will be used to determine the need
6942 -- for extra formals.
6944 if Is_Overloadable (E) and then Present (Alias (E)) then
6945 P_Formal := First_Formal (Alias (E));
6946 end if;
6948 Last_Extra := Empty;
6949 Formal := First_Formal (E);
6950 while Present (Formal) loop
6951 Last_Extra := Formal;
6952 Next_Formal (Formal);
6953 end loop;
6955 -- If Extra_formals were already created, don't do it again. This
6956 -- situation may arise for subprogram types created as part of
6957 -- dispatching calls (see Expand_Dispatching_Call)
6959 if Present (Last_Extra) and then Present (Extra_Formal (Last_Extra)) then
6960 return;
6961 end if;
6963 -- If the subprogram is a predefined dispatching subprogram then don't
6964 -- generate any extra constrained or accessibility level formals. In
6965 -- general we suppress these for internal subprograms (by not calling
6966 -- Freeze_Subprogram and Create_Extra_Formals at all), but internally
6967 -- generated stream attributes do get passed through because extra
6968 -- build-in-place formals are needed in some cases (limited 'Input).
6970 if Is_Predefined_Internal_Operation (E) then
6971 goto Test_For_Func_Result_Extras;
6972 end if;
6974 Formal := First_Formal (E);
6975 while Present (Formal) loop
6977 -- Create extra formal for supporting the attribute 'Constrained.
6978 -- The case of a private type view without discriminants also
6979 -- requires the extra formal if the underlying type has defaulted
6980 -- discriminants.
6982 if Ekind (Formal) /= E_In_Parameter then
6983 if Present (P_Formal) then
6984 Formal_Type := Etype (P_Formal);
6985 else
6986 Formal_Type := Etype (Formal);
6987 end if;
6989 -- Do not produce extra formals for Unchecked_Union parameters.
6990 -- Jump directly to the end of the loop.
6992 if Is_Unchecked_Union (Base_Type (Formal_Type)) then
6993 goto Skip_Extra_Formal_Generation;
6994 end if;
6996 if not Has_Discriminants (Formal_Type)
6997 and then Ekind (Formal_Type) in Private_Kind
6998 and then Present (Underlying_Type (Formal_Type))
6999 then
7000 Formal_Type := Underlying_Type (Formal_Type);
7001 end if;
7003 -- Suppress the extra formal if formal's subtype is constrained or
7004 -- indefinite, or we're compiling for Ada 2012 and the underlying
7005 -- type is tagged and limited. In Ada 2012, a limited tagged type
7006 -- can have defaulted discriminants, but 'Constrained is required
7007 -- to return True, so the formal is never needed (see AI05-0214).
7008 -- Note that this ensures consistency of calling sequences for
7009 -- dispatching operations when some types in a class have defaults
7010 -- on discriminants and others do not (and requiring the extra
7011 -- formal would introduce distributed overhead).
7013 -- If the type does not have a completion yet, treat as prior to
7014 -- Ada 2012 for consistency.
7016 if Has_Discriminants (Formal_Type)
7017 and then not Is_Constrained (Formal_Type)
7018 and then not Is_Indefinite_Subtype (Formal_Type)
7019 and then (Ada_Version < Ada_2012
7020 or else No (Underlying_Type (Formal_Type))
7021 or else not
7022 (Is_Limited_Type (Formal_Type)
7023 and then
7024 (Is_Tagged_Type
7025 (Underlying_Type (Formal_Type)))))
7026 then
7027 Set_Extra_Constrained
7028 (Formal, Add_Extra_Formal (Formal, Standard_Boolean, E, "O"));
7029 end if;
7030 end if;
7032 -- Create extra formal for supporting accessibility checking. This
7033 -- is done for both anonymous access formals and formals of named
7034 -- access types that are marked as controlling formals. The latter
7035 -- case can occur when Expand_Dispatching_Call creates a subprogram
7036 -- type and substitutes the types of access-to-class-wide actuals
7037 -- for the anonymous access-to-specific-type of controlling formals.
7038 -- Base_Type is applied because in cases where there is a null
7039 -- exclusion the formal may have an access subtype.
7041 -- This is suppressed if we specifically suppress accessibility
7042 -- checks at the package level for either the subprogram, or the
7043 -- package in which it resides. However, we do not suppress it
7044 -- simply if the scope has accessibility checks suppressed, since
7045 -- this could cause trouble when clients are compiled with a
7046 -- different suppression setting. The explicit checks at the
7047 -- package level are safe from this point of view.
7049 if (Ekind (Base_Type (Etype (Formal))) = E_Anonymous_Access_Type
7050 or else (Is_Controlling_Formal (Formal)
7051 and then Is_Access_Type (Base_Type (Etype (Formal)))))
7052 and then not
7053 (Explicit_Suppress (E, Accessibility_Check)
7054 or else
7055 Explicit_Suppress (Scope (E), Accessibility_Check))
7056 and then
7057 (No (P_Formal)
7058 or else Present (Extra_Accessibility (P_Formal)))
7059 then
7060 Set_Extra_Accessibility
7061 (Formal, Add_Extra_Formal (Formal, Standard_Natural, E, "L"));
7062 end if;
7064 -- This label is required when skipping extra formal generation for
7065 -- Unchecked_Union parameters.
7067 <<Skip_Extra_Formal_Generation>>
7069 if Present (P_Formal) then
7070 Next_Formal (P_Formal);
7071 end if;
7073 Next_Formal (Formal);
7074 end loop;
7076 <<Test_For_Func_Result_Extras>>
7078 -- Ada 2012 (AI05-234): "the accessibility level of the result of a
7079 -- function call is ... determined by the point of call ...".
7081 if Needs_Result_Accessibility_Level (E) then
7082 Set_Extra_Accessibility_Of_Result
7083 (E, Add_Extra_Formal (E, Standard_Natural, E, "L"));
7084 end if;
7086 -- Ada 2005 (AI-318-02): In the case of build-in-place functions, add
7087 -- appropriate extra formals. See type Exp_Ch6.BIP_Formal_Kind.
7089 if Ada_Version >= Ada_2005 and then Is_Build_In_Place_Function (E) then
7090 declare
7091 Result_Subt : constant Entity_Id := Etype (E);
7092 Full_Subt : constant Entity_Id := Available_View (Result_Subt);
7093 Formal_Typ : Entity_Id;
7095 Discard : Entity_Id;
7096 pragma Warnings (Off, Discard);
7098 begin
7099 -- In the case of functions with unconstrained result subtypes,
7100 -- add a 4-state formal indicating whether the return object is
7101 -- allocated by the caller (1), or should be allocated by the
7102 -- callee on the secondary stack (2), in the global heap (3), or
7103 -- in a user-defined storage pool (4). For the moment we just use
7104 -- Natural for the type of this formal. Note that this formal
7105 -- isn't usually needed in the case where the result subtype is
7106 -- constrained, but it is needed when the function has a tagged
7107 -- result, because generally such functions can be called in a
7108 -- dispatching context and such calls must be handled like calls
7109 -- to a class-wide function.
7111 if Needs_BIP_Alloc_Form (E) then
7112 Discard :=
7113 Add_Extra_Formal
7114 (E, Standard_Natural,
7115 E, BIP_Formal_Suffix (BIP_Alloc_Form));
7117 -- Add BIP_Storage_Pool, in case BIP_Alloc_Form indicates to
7118 -- use a user-defined pool. This formal is not added on
7119 -- .NET/JVM/ZFP as those targets do not support pools.
7121 if VM_Target = No_VM
7122 and then RTE_Available (RE_Root_Storage_Pool_Ptr)
7123 then
7124 Discard :=
7125 Add_Extra_Formal
7126 (E, RTE (RE_Root_Storage_Pool_Ptr),
7127 E, BIP_Formal_Suffix (BIP_Storage_Pool));
7128 end if;
7129 end if;
7131 -- In the case of functions whose result type needs finalization,
7132 -- add an extra formal which represents the finalization master.
7134 if Needs_BIP_Finalization_Master (E) then
7135 Discard :=
7136 Add_Extra_Formal
7137 (E, RTE (RE_Finalization_Master_Ptr),
7138 E, BIP_Formal_Suffix (BIP_Finalization_Master));
7139 end if;
7141 -- When the result type contains tasks, add two extra formals: the
7142 -- master of the tasks to be created, and the caller's activation
7143 -- chain.
7145 if Has_Task (Full_Subt) then
7146 Discard :=
7147 Add_Extra_Formal
7148 (E, RTE (RE_Master_Id),
7149 E, BIP_Formal_Suffix (BIP_Task_Master));
7150 Discard :=
7151 Add_Extra_Formal
7152 (E, RTE (RE_Activation_Chain_Access),
7153 E, BIP_Formal_Suffix (BIP_Activation_Chain));
7154 end if;
7156 -- All build-in-place functions get an extra formal that will be
7157 -- passed the address of the return object within the caller.
7159 Formal_Typ :=
7160 Create_Itype (E_Anonymous_Access_Type, E, Scope_Id => Scope (E));
7162 Set_Directly_Designated_Type (Formal_Typ, Result_Subt);
7163 Set_Etype (Formal_Typ, Formal_Typ);
7164 Set_Depends_On_Private
7165 (Formal_Typ, Has_Private_Component (Formal_Typ));
7166 Set_Is_Public (Formal_Typ, Is_Public (Scope (Formal_Typ)));
7167 Set_Is_Access_Constant (Formal_Typ, False);
7169 -- Ada 2005 (AI-50217): Propagate the attribute that indicates
7170 -- the designated type comes from the limited view (for back-end
7171 -- purposes).
7173 Set_From_Limited_With
7174 (Formal_Typ, From_Limited_With (Result_Subt));
7176 Layout_Type (Formal_Typ);
7178 Discard :=
7179 Add_Extra_Formal
7180 (E, Formal_Typ, E, BIP_Formal_Suffix (BIP_Object_Access));
7181 end;
7182 end if;
7183 end Create_Extra_Formals;
7185 -----------------------------
7186 -- Enter_Overloaded_Entity --
7187 -----------------------------
7189 procedure Enter_Overloaded_Entity (S : Entity_Id) is
7190 E : Entity_Id := Current_Entity_In_Scope (S);
7191 C_E : Entity_Id := Current_Entity (S);
7193 begin
7194 if Present (E) then
7195 Set_Has_Homonym (E);
7196 Set_Has_Homonym (S);
7197 end if;
7199 Set_Is_Immediately_Visible (S);
7200 Set_Scope (S, Current_Scope);
7202 -- Chain new entity if front of homonym in current scope, so that
7203 -- homonyms are contiguous.
7205 if Present (E) and then E /= C_E then
7206 while Homonym (C_E) /= E loop
7207 C_E := Homonym (C_E);
7208 end loop;
7210 Set_Homonym (C_E, S);
7212 else
7213 E := C_E;
7214 Set_Current_Entity (S);
7215 end if;
7217 Set_Homonym (S, E);
7219 if Is_Inherited_Operation (S) then
7220 Append_Inherited_Subprogram (S);
7221 else
7222 Append_Entity (S, Current_Scope);
7223 end if;
7225 Set_Public_Status (S);
7227 if Debug_Flag_E then
7228 Write_Str ("New overloaded entity chain: ");
7229 Write_Name (Chars (S));
7231 E := S;
7232 while Present (E) loop
7233 Write_Str (" "); Write_Int (Int (E));
7234 E := Homonym (E);
7235 end loop;
7237 Write_Eol;
7238 end if;
7240 -- Generate warning for hiding
7242 if Warn_On_Hiding
7243 and then Comes_From_Source (S)
7244 and then In_Extended_Main_Source_Unit (S)
7245 then
7246 E := S;
7247 loop
7248 E := Homonym (E);
7249 exit when No (E);
7251 -- Warn unless genuine overloading. Do not emit warning on
7252 -- hiding predefined operators in Standard (these are either an
7253 -- (artifact of our implicit declarations, or simple noise) but
7254 -- keep warning on a operator defined on a local subtype, because
7255 -- of the real danger that different operators may be applied in
7256 -- various parts of the program.
7258 -- Note that if E and S have the same scope, there is never any
7259 -- hiding. Either the two conflict, and the program is illegal,
7260 -- or S is overriding an implicit inherited subprogram.
7262 if Scope (E) /= Scope (S)
7263 and then (not Is_Overloadable (E)
7264 or else Subtype_Conformant (E, S))
7265 and then (Is_Immediately_Visible (E)
7266 or else
7267 Is_Potentially_Use_Visible (S))
7268 then
7269 if Scope (E) /= Standard_Standard then
7270 Error_Msg_Sloc := Sloc (E);
7271 Error_Msg_N ("declaration of & hides one #?h?", S);
7273 elsif Nkind (S) = N_Defining_Operator_Symbol
7274 and then
7275 Scope (Base_Type (Etype (First_Formal (S)))) /= Scope (S)
7276 then
7277 Error_Msg_N
7278 ("declaration of & hides predefined operator?h?", S);
7279 end if;
7280 end if;
7281 end loop;
7282 end if;
7283 end Enter_Overloaded_Entity;
7285 -----------------------------
7286 -- Check_Untagged_Equality --
7287 -----------------------------
7289 procedure Check_Untagged_Equality (Eq_Op : Entity_Id) is
7290 Typ : constant Entity_Id := Etype (First_Formal (Eq_Op));
7291 Decl : constant Node_Id := Unit_Declaration_Node (Eq_Op);
7292 Obj_Decl : Node_Id;
7294 begin
7295 -- This check applies only if we have a subprogram declaration with an
7296 -- untagged record type.
7298 if Nkind (Decl) /= N_Subprogram_Declaration
7299 or else not Is_Record_Type (Typ)
7300 or else Is_Tagged_Type (Typ)
7301 then
7302 return;
7303 end if;
7305 -- In Ada 2012 case, we will output errors or warnings depending on
7306 -- the setting of debug flag -gnatd.E.
7308 if Ada_Version >= Ada_2012 then
7309 Error_Msg_Warn := Debug_Flag_Dot_EE;
7311 -- In earlier versions of Ada, nothing to do unless we are warning on
7312 -- Ada 2012 incompatibilities (Warn_On_Ada_2012_Incompatibility set).
7314 else
7315 if not Warn_On_Ada_2012_Compatibility then
7316 return;
7317 end if;
7318 end if;
7320 -- Cases where the type has already been frozen
7322 if Is_Frozen (Typ) then
7324 -- If the type is not declared in a package, or if we are in the body
7325 -- of the package or in some other scope, the new operation is not
7326 -- primitive, and therefore legal, though suspicious. Should we
7327 -- generate a warning in this case ???
7329 if Ekind (Scope (Typ)) /= E_Package
7330 or else Scope (Typ) /= Current_Scope
7331 then
7332 return;
7334 -- If the type is a generic actual (sub)type, the operation is not
7335 -- primitive either because the base type is declared elsewhere.
7337 elsif Is_Generic_Actual_Type (Typ) then
7338 return;
7340 -- Here we have a definite error of declaration after freezing
7342 else
7343 if Ada_Version >= Ada_2012 then
7344 Error_Msg_NE
7345 ("equality operator must be declared before type & is "
7346 & "frozen (RM 4.5.2 (9.8)) (Ada 2012)<<", Eq_Op, Typ);
7348 -- In Ada 2012 mode with error turned to warning, output one
7349 -- more warning to warn that the equality operation may not
7350 -- compose. This is the consequence of ignoring the error.
7352 if Error_Msg_Warn then
7353 Error_Msg_N ("\equality operation may not compose??", Eq_Op);
7354 end if;
7356 else
7357 Error_Msg_NE
7358 ("equality operator must be declared before type& is "
7359 & "frozen (RM 4.5.2 (9.8)) (Ada 2012)?y?", Eq_Op, Typ);
7360 end if;
7362 -- If we are in the package body, we could just move the
7363 -- declaration to the package spec, so add a message saying that.
7365 if In_Package_Body (Scope (Typ)) then
7366 if Ada_Version >= Ada_2012 then
7367 Error_Msg_N
7368 ("\move declaration to package spec<<", Eq_Op);
7369 else
7370 Error_Msg_N
7371 ("\move declaration to package spec (Ada 2012)?y?", Eq_Op);
7372 end if;
7374 -- Otherwise try to find the freezing point
7376 else
7377 Obj_Decl := Next (Parent (Typ));
7378 while Present (Obj_Decl) and then Obj_Decl /= Decl loop
7379 if Nkind (Obj_Decl) = N_Object_Declaration
7380 and then Etype (Defining_Identifier (Obj_Decl)) = Typ
7381 then
7382 -- Freezing point, output warnings
7384 if Ada_Version >= Ada_2012 then
7385 Error_Msg_NE
7386 ("type& is frozen by declaration??", Obj_Decl, Typ);
7387 Error_Msg_N
7388 ("\an equality operator cannot be declared after "
7389 & "this point??",
7390 Obj_Decl);
7391 else
7392 Error_Msg_NE
7393 ("type& is frozen by declaration (Ada 2012)?y?",
7394 Obj_Decl, Typ);
7395 Error_Msg_N
7396 ("\an equality operator cannot be declared after "
7397 & "this point (Ada 2012)?y?",
7398 Obj_Decl);
7399 end if;
7401 exit;
7402 end if;
7404 Next (Obj_Decl);
7405 end loop;
7406 end if;
7407 end if;
7409 -- Here if type is not frozen yet. It is illegal to have a primitive
7410 -- equality declared in the private part if the type is visible.
7412 elsif not In_Same_List (Parent (Typ), Decl)
7413 and then not Is_Limited_Type (Typ)
7414 then
7415 -- Shouldn't we give an RM reference here???
7417 if Ada_Version >= Ada_2012 then
7418 Error_Msg_N
7419 ("equality operator appears too late<<", Eq_Op);
7420 else
7421 Error_Msg_N
7422 ("equality operator appears too late (Ada 2012)?y?", Eq_Op);
7423 end if;
7425 -- No error detected
7427 else
7428 return;
7429 end if;
7430 end Check_Untagged_Equality;
7432 -----------------------------
7433 -- Find_Corresponding_Spec --
7434 -----------------------------
7436 function Find_Corresponding_Spec
7437 (N : Node_Id;
7438 Post_Error : Boolean := True) return Entity_Id
7440 Spec : constant Node_Id := Specification (N);
7441 Designator : constant Entity_Id := Defining_Entity (Spec);
7443 E : Entity_Id;
7445 function Different_Generic_Profile (E : Entity_Id) return Boolean;
7446 -- Even if fully conformant, a body may depend on a generic actual when
7447 -- the spec does not, or vice versa, in which case they were distinct
7448 -- entities in the generic.
7450 -------------------------------
7451 -- Different_Generic_Profile --
7452 -------------------------------
7454 function Different_Generic_Profile (E : Entity_Id) return Boolean is
7455 F1, F2 : Entity_Id;
7457 function Same_Generic_Actual (T1, T2 : Entity_Id) return Boolean;
7458 -- Check that the types of corresponding formals have the same
7459 -- generic actual if any. We have to account for subtypes of a
7460 -- generic formal, declared between a spec and a body, which may
7461 -- appear distinct in an instance but matched in the generic, and
7462 -- the subtype may be used either in the spec or the body of the
7463 -- subprogram being checked.
7465 -------------------------
7466 -- Same_Generic_Actual --
7467 -------------------------
7469 function Same_Generic_Actual (T1, T2 : Entity_Id) return Boolean is
7471 function Is_Declared_Subtype (S1, S2 : Entity_Id) return Boolean;
7472 -- Predicate to check whether S1 is a subtype of S2 in the source
7473 -- of the instance.
7475 -------------------------
7476 -- Is_Declared_Subtype --
7477 -------------------------
7479 function Is_Declared_Subtype (S1, S2 : Entity_Id) return Boolean is
7480 begin
7481 return Comes_From_Source (Parent (S1))
7482 and then Nkind (Parent (S1)) = N_Subtype_Declaration
7483 and then Is_Entity_Name (Subtype_Indication (Parent (S1)))
7484 and then Entity (Subtype_Indication (Parent (S1))) = S2;
7485 end Is_Declared_Subtype;
7487 -- Start of processing for Same_Generic_Actual
7489 begin
7490 return Is_Generic_Actual_Type (T1) = Is_Generic_Actual_Type (T2)
7491 or else Is_Declared_Subtype (T1, T2)
7492 or else Is_Declared_Subtype (T2, T1);
7493 end Same_Generic_Actual;
7495 -- Start of processing for Different_Generic_Profile
7497 begin
7498 if not In_Instance then
7499 return False;
7501 elsif Ekind (E) = E_Function
7502 and then not Same_Generic_Actual (Etype (E), Etype (Designator))
7503 then
7504 return True;
7505 end if;
7507 F1 := First_Formal (Designator);
7508 F2 := First_Formal (E);
7509 while Present (F1) loop
7510 if not Same_Generic_Actual (Etype (F1), Etype (F2)) then
7511 return True;
7512 end if;
7514 Next_Formal (F1);
7515 Next_Formal (F2);
7516 end loop;
7518 return False;
7519 end Different_Generic_Profile;
7521 -- Start of processing for Find_Corresponding_Spec
7523 begin
7524 E := Current_Entity (Designator);
7525 while Present (E) loop
7527 -- We are looking for a matching spec. It must have the same scope,
7528 -- and the same name, and either be type conformant, or be the case
7529 -- of a library procedure spec and its body (which belong to one
7530 -- another regardless of whether they are type conformant or not).
7532 if Scope (E) = Current_Scope then
7533 if Current_Scope = Standard_Standard
7534 or else (Ekind (E) = Ekind (Designator)
7535 and then Type_Conformant (E, Designator))
7536 then
7537 -- Within an instantiation, we know that spec and body are
7538 -- subtype conformant, because they were subtype conformant in
7539 -- the generic. We choose the subtype-conformant entity here as
7540 -- well, to resolve spurious ambiguities in the instance that
7541 -- were not present in the generic (i.e. when two different
7542 -- types are given the same actual). If we are looking for a
7543 -- spec to match a body, full conformance is expected.
7545 if In_Instance then
7547 -- Inherit the convention and "ghostness" of the matching
7548 -- spec to ensure proper full and subtype conformance.
7550 Set_Convention (Designator, Convention (E));
7552 if Is_Ghost_Entity (E) then
7553 Set_Is_Ghost_Entity (Designator);
7554 end if;
7556 -- Skip past subprogram bodies and subprogram renamings that
7557 -- may appear to have a matching spec, but that aren't fully
7558 -- conformant with it. That can occur in cases where an
7559 -- actual type causes unrelated homographs in the instance.
7561 if Nkind_In (N, N_Subprogram_Body,
7562 N_Subprogram_Renaming_Declaration)
7563 and then Present (Homonym (E))
7564 and then not Fully_Conformant (Designator, E)
7565 then
7566 goto Next_Entity;
7568 elsif not Subtype_Conformant (Designator, E) then
7569 goto Next_Entity;
7571 elsif Different_Generic_Profile (E) then
7572 goto Next_Entity;
7573 end if;
7574 end if;
7576 -- Ada 2012 (AI05-0165): For internally generated bodies of
7577 -- null procedures locate the internally generated spec. We
7578 -- enforce mode conformance since a tagged type may inherit
7579 -- from interfaces several null primitives which differ only
7580 -- in the mode of the formals.
7582 if not (Comes_From_Source (E))
7583 and then Is_Null_Procedure (E)
7584 and then not Mode_Conformant (Designator, E)
7585 then
7586 null;
7588 -- For null procedures coming from source that are completions,
7589 -- analysis of the generated body will establish the link.
7591 elsif Comes_From_Source (E)
7592 and then Nkind (Spec) = N_Procedure_Specification
7593 and then Null_Present (Spec)
7594 then
7595 return E;
7597 elsif not Has_Completion (E) then
7598 if Nkind (N) /= N_Subprogram_Body_Stub then
7599 Set_Corresponding_Spec (N, E);
7600 end if;
7602 Set_Has_Completion (E);
7603 return E;
7605 elsif Nkind (Parent (N)) = N_Subunit then
7607 -- If this is the proper body of a subunit, the completion
7608 -- flag is set when analyzing the stub.
7610 return E;
7612 -- If E is an internal function with a controlling result that
7613 -- was created for an operation inherited by a null extension,
7614 -- it may be overridden by a body without a previous spec (one
7615 -- more reason why these should be shunned). In that case we
7616 -- remove the generated body if present, because the current
7617 -- one is the explicit overriding.
7619 elsif Ekind (E) = E_Function
7620 and then Ada_Version >= Ada_2005
7621 and then not Comes_From_Source (E)
7622 and then Has_Controlling_Result (E)
7623 and then Is_Null_Extension (Etype (E))
7624 and then Comes_From_Source (Spec)
7625 then
7626 Set_Has_Completion (E, False);
7628 if Expander_Active
7629 and then Nkind (Parent (E)) = N_Function_Specification
7630 then
7631 Remove
7632 (Unit_Declaration_Node
7633 (Corresponding_Body (Unit_Declaration_Node (E))));
7635 return E;
7637 -- If expansion is disabled, or if the wrapper function has
7638 -- not been generated yet, this a late body overriding an
7639 -- inherited operation, or it is an overriding by some other
7640 -- declaration before the controlling result is frozen. In
7641 -- either case this is a declaration of a new entity.
7643 else
7644 return Empty;
7645 end if;
7647 -- If the body already exists, then this is an error unless
7648 -- the previous declaration is the implicit declaration of a
7649 -- derived subprogram. It is also legal for an instance to
7650 -- contain type conformant overloadable declarations (but the
7651 -- generic declaration may not), per 8.3(26/2).
7653 elsif No (Alias (E))
7654 and then not Is_Intrinsic_Subprogram (E)
7655 and then not In_Instance
7656 and then Post_Error
7657 then
7658 Error_Msg_Sloc := Sloc (E);
7660 if Is_Imported (E) then
7661 Error_Msg_NE
7662 ("body not allowed for imported subprogram & declared#",
7663 N, E);
7664 else
7665 Error_Msg_NE ("duplicate body for & declared#", N, E);
7666 end if;
7667 end if;
7669 -- Child units cannot be overloaded, so a conformance mismatch
7670 -- between body and a previous spec is an error.
7672 elsif Is_Child_Unit (E)
7673 and then
7674 Nkind (Unit_Declaration_Node (Designator)) = N_Subprogram_Body
7675 and then
7676 Nkind (Parent (Unit_Declaration_Node (Designator))) =
7677 N_Compilation_Unit
7678 and then Post_Error
7679 then
7680 Error_Msg_N
7681 ("body of child unit does not match previous declaration", N);
7682 end if;
7683 end if;
7685 <<Next_Entity>>
7686 E := Homonym (E);
7687 end loop;
7689 -- On exit, we know that no previous declaration of subprogram exists
7691 return Empty;
7692 end Find_Corresponding_Spec;
7694 ----------------------
7695 -- Fully_Conformant --
7696 ----------------------
7698 function Fully_Conformant (New_Id, Old_Id : Entity_Id) return Boolean is
7699 Result : Boolean;
7700 begin
7701 Check_Conformance (New_Id, Old_Id, Fully_Conformant, False, Result);
7702 return Result;
7703 end Fully_Conformant;
7705 ----------------------------------
7706 -- Fully_Conformant_Expressions --
7707 ----------------------------------
7709 function Fully_Conformant_Expressions
7710 (Given_E1 : Node_Id;
7711 Given_E2 : Node_Id) return Boolean
7713 E1 : constant Node_Id := Original_Node (Given_E1);
7714 E2 : constant Node_Id := Original_Node (Given_E2);
7715 -- We always test conformance on original nodes, since it is possible
7716 -- for analysis and/or expansion to make things look as though they
7717 -- conform when they do not, e.g. by converting 1+2 into 3.
7719 function FCE (Given_E1, Given_E2 : Node_Id) return Boolean
7720 renames Fully_Conformant_Expressions;
7722 function FCL (L1, L2 : List_Id) return Boolean;
7723 -- Compare elements of two lists for conformance. Elements have to be
7724 -- conformant, and actuals inserted as default parameters do not match
7725 -- explicit actuals with the same value.
7727 function FCO (Op_Node, Call_Node : Node_Id) return Boolean;
7728 -- Compare an operator node with a function call
7730 ---------
7731 -- FCL --
7732 ---------
7734 function FCL (L1, L2 : List_Id) return Boolean is
7735 N1, N2 : Node_Id;
7737 begin
7738 if L1 = No_List then
7739 N1 := Empty;
7740 else
7741 N1 := First (L1);
7742 end if;
7744 if L2 = No_List then
7745 N2 := Empty;
7746 else
7747 N2 := First (L2);
7748 end if;
7750 -- Compare two lists, skipping rewrite insertions (we want to compare
7751 -- the original trees, not the expanded versions).
7753 loop
7754 if Is_Rewrite_Insertion (N1) then
7755 Next (N1);
7756 elsif Is_Rewrite_Insertion (N2) then
7757 Next (N2);
7758 elsif No (N1) then
7759 return No (N2);
7760 elsif No (N2) then
7761 return False;
7762 elsif not FCE (N1, N2) then
7763 return False;
7764 else
7765 Next (N1);
7766 Next (N2);
7767 end if;
7768 end loop;
7769 end FCL;
7771 ---------
7772 -- FCO --
7773 ---------
7775 function FCO (Op_Node, Call_Node : Node_Id) return Boolean is
7776 Actuals : constant List_Id := Parameter_Associations (Call_Node);
7777 Act : Node_Id;
7779 begin
7780 if No (Actuals)
7781 or else Entity (Op_Node) /= Entity (Name (Call_Node))
7782 then
7783 return False;
7785 else
7786 Act := First (Actuals);
7788 if Nkind (Op_Node) in N_Binary_Op then
7789 if not FCE (Left_Opnd (Op_Node), Act) then
7790 return False;
7791 end if;
7793 Next (Act);
7794 end if;
7796 return Present (Act)
7797 and then FCE (Right_Opnd (Op_Node), Act)
7798 and then No (Next (Act));
7799 end if;
7800 end FCO;
7802 -- Start of processing for Fully_Conformant_Expressions
7804 begin
7805 -- Non-conformant if paren count does not match. Note: if some idiot
7806 -- complains that we don't do this right for more than 3 levels of
7807 -- parentheses, they will be treated with the respect they deserve.
7809 if Paren_Count (E1) /= Paren_Count (E2) then
7810 return False;
7812 -- If same entities are referenced, then they are conformant even if
7813 -- they have different forms (RM 8.3.1(19-20)).
7815 elsif Is_Entity_Name (E1) and then Is_Entity_Name (E2) then
7816 if Present (Entity (E1)) then
7817 return Entity (E1) = Entity (E2)
7818 or else (Chars (Entity (E1)) = Chars (Entity (E2))
7819 and then Ekind (Entity (E1)) = E_Discriminant
7820 and then Ekind (Entity (E2)) = E_In_Parameter);
7822 elsif Nkind (E1) = N_Expanded_Name
7823 and then Nkind (E2) = N_Expanded_Name
7824 and then Nkind (Selector_Name (E1)) = N_Character_Literal
7825 and then Nkind (Selector_Name (E2)) = N_Character_Literal
7826 then
7827 return Chars (Selector_Name (E1)) = Chars (Selector_Name (E2));
7829 else
7830 -- Identifiers in component associations don't always have
7831 -- entities, but their names must conform.
7833 return Nkind (E1) = N_Identifier
7834 and then Nkind (E2) = N_Identifier
7835 and then Chars (E1) = Chars (E2);
7836 end if;
7838 elsif Nkind (E1) = N_Character_Literal
7839 and then Nkind (E2) = N_Expanded_Name
7840 then
7841 return Nkind (Selector_Name (E2)) = N_Character_Literal
7842 and then Chars (E1) = Chars (Selector_Name (E2));
7844 elsif Nkind (E2) = N_Character_Literal
7845 and then Nkind (E1) = N_Expanded_Name
7846 then
7847 return Nkind (Selector_Name (E1)) = N_Character_Literal
7848 and then Chars (E2) = Chars (Selector_Name (E1));
7850 elsif Nkind (E1) in N_Op and then Nkind (E2) = N_Function_Call then
7851 return FCO (E1, E2);
7853 elsif Nkind (E2) in N_Op and then Nkind (E1) = N_Function_Call then
7854 return FCO (E2, E1);
7856 -- Otherwise we must have the same syntactic entity
7858 elsif Nkind (E1) /= Nkind (E2) then
7859 return False;
7861 -- At this point, we specialize by node type
7863 else
7864 case Nkind (E1) is
7866 when N_Aggregate =>
7867 return
7868 FCL (Expressions (E1), Expressions (E2))
7869 and then
7870 FCL (Component_Associations (E1),
7871 Component_Associations (E2));
7873 when N_Allocator =>
7874 if Nkind (Expression (E1)) = N_Qualified_Expression
7875 or else
7876 Nkind (Expression (E2)) = N_Qualified_Expression
7877 then
7878 return FCE (Expression (E1), Expression (E2));
7880 -- Check that the subtype marks and any constraints
7881 -- are conformant
7883 else
7884 declare
7885 Indic1 : constant Node_Id := Expression (E1);
7886 Indic2 : constant Node_Id := Expression (E2);
7887 Elt1 : Node_Id;
7888 Elt2 : Node_Id;
7890 begin
7891 if Nkind (Indic1) /= N_Subtype_Indication then
7892 return
7893 Nkind (Indic2) /= N_Subtype_Indication
7894 and then Entity (Indic1) = Entity (Indic2);
7896 elsif Nkind (Indic2) /= N_Subtype_Indication then
7897 return
7898 Nkind (Indic1) /= N_Subtype_Indication
7899 and then Entity (Indic1) = Entity (Indic2);
7901 else
7902 if Entity (Subtype_Mark (Indic1)) /=
7903 Entity (Subtype_Mark (Indic2))
7904 then
7905 return False;
7906 end if;
7908 Elt1 := First (Constraints (Constraint (Indic1)));
7909 Elt2 := First (Constraints (Constraint (Indic2)));
7910 while Present (Elt1) and then Present (Elt2) loop
7911 if not FCE (Elt1, Elt2) then
7912 return False;
7913 end if;
7915 Next (Elt1);
7916 Next (Elt2);
7917 end loop;
7919 return True;
7920 end if;
7921 end;
7922 end if;
7924 when N_Attribute_Reference =>
7925 return
7926 Attribute_Name (E1) = Attribute_Name (E2)
7927 and then FCL (Expressions (E1), Expressions (E2));
7929 when N_Binary_Op =>
7930 return
7931 Entity (E1) = Entity (E2)
7932 and then FCE (Left_Opnd (E1), Left_Opnd (E2))
7933 and then FCE (Right_Opnd (E1), Right_Opnd (E2));
7935 when N_Short_Circuit | N_Membership_Test =>
7936 return
7937 FCE (Left_Opnd (E1), Left_Opnd (E2))
7938 and then
7939 FCE (Right_Opnd (E1), Right_Opnd (E2));
7941 when N_Case_Expression =>
7942 declare
7943 Alt1 : Node_Id;
7944 Alt2 : Node_Id;
7946 begin
7947 if not FCE (Expression (E1), Expression (E2)) then
7948 return False;
7950 else
7951 Alt1 := First (Alternatives (E1));
7952 Alt2 := First (Alternatives (E2));
7953 loop
7954 if Present (Alt1) /= Present (Alt2) then
7955 return False;
7956 elsif No (Alt1) then
7957 return True;
7958 end if;
7960 if not FCE (Expression (Alt1), Expression (Alt2))
7961 or else not FCL (Discrete_Choices (Alt1),
7962 Discrete_Choices (Alt2))
7963 then
7964 return False;
7965 end if;
7967 Next (Alt1);
7968 Next (Alt2);
7969 end loop;
7970 end if;
7971 end;
7973 when N_Character_Literal =>
7974 return
7975 Char_Literal_Value (E1) = Char_Literal_Value (E2);
7977 when N_Component_Association =>
7978 return
7979 FCL (Choices (E1), Choices (E2))
7980 and then
7981 FCE (Expression (E1), Expression (E2));
7983 when N_Explicit_Dereference =>
7984 return
7985 FCE (Prefix (E1), Prefix (E2));
7987 when N_Extension_Aggregate =>
7988 return
7989 FCL (Expressions (E1), Expressions (E2))
7990 and then Null_Record_Present (E1) =
7991 Null_Record_Present (E2)
7992 and then FCL (Component_Associations (E1),
7993 Component_Associations (E2));
7995 when N_Function_Call =>
7996 return
7997 FCE (Name (E1), Name (E2))
7998 and then
7999 FCL (Parameter_Associations (E1),
8000 Parameter_Associations (E2));
8002 when N_If_Expression =>
8003 return
8004 FCL (Expressions (E1), Expressions (E2));
8006 when N_Indexed_Component =>
8007 return
8008 FCE (Prefix (E1), Prefix (E2))
8009 and then
8010 FCL (Expressions (E1), Expressions (E2));
8012 when N_Integer_Literal =>
8013 return (Intval (E1) = Intval (E2));
8015 when N_Null =>
8016 return True;
8018 when N_Operator_Symbol =>
8019 return
8020 Chars (E1) = Chars (E2);
8022 when N_Others_Choice =>
8023 return True;
8025 when N_Parameter_Association =>
8026 return
8027 Chars (Selector_Name (E1)) = Chars (Selector_Name (E2))
8028 and then FCE (Explicit_Actual_Parameter (E1),
8029 Explicit_Actual_Parameter (E2));
8031 when N_Qualified_Expression =>
8032 return
8033 FCE (Subtype_Mark (E1), Subtype_Mark (E2))
8034 and then
8035 FCE (Expression (E1), Expression (E2));
8037 when N_Quantified_Expression =>
8038 if not FCE (Condition (E1), Condition (E2)) then
8039 return False;
8040 end if;
8042 if Present (Loop_Parameter_Specification (E1))
8043 and then Present (Loop_Parameter_Specification (E2))
8044 then
8045 declare
8046 L1 : constant Node_Id :=
8047 Loop_Parameter_Specification (E1);
8048 L2 : constant Node_Id :=
8049 Loop_Parameter_Specification (E2);
8051 begin
8052 return
8053 Reverse_Present (L1) = Reverse_Present (L2)
8054 and then
8055 FCE (Defining_Identifier (L1),
8056 Defining_Identifier (L2))
8057 and then
8058 FCE (Discrete_Subtype_Definition (L1),
8059 Discrete_Subtype_Definition (L2));
8060 end;
8062 elsif Present (Iterator_Specification (E1))
8063 and then Present (Iterator_Specification (E2))
8064 then
8065 declare
8066 I1 : constant Node_Id := Iterator_Specification (E1);
8067 I2 : constant Node_Id := Iterator_Specification (E2);
8069 begin
8070 return
8071 FCE (Defining_Identifier (I1),
8072 Defining_Identifier (I2))
8073 and then
8074 Of_Present (I1) = Of_Present (I2)
8075 and then
8076 Reverse_Present (I1) = Reverse_Present (I2)
8077 and then FCE (Name (I1), Name (I2))
8078 and then FCE (Subtype_Indication (I1),
8079 Subtype_Indication (I2));
8080 end;
8082 -- The quantified expressions used different specifications to
8083 -- walk their respective ranges.
8085 else
8086 return False;
8087 end if;
8089 when N_Range =>
8090 return
8091 FCE (Low_Bound (E1), Low_Bound (E2))
8092 and then
8093 FCE (High_Bound (E1), High_Bound (E2));
8095 when N_Real_Literal =>
8096 return (Realval (E1) = Realval (E2));
8098 when N_Selected_Component =>
8099 return
8100 FCE (Prefix (E1), Prefix (E2))
8101 and then
8102 FCE (Selector_Name (E1), Selector_Name (E2));
8104 when N_Slice =>
8105 return
8106 FCE (Prefix (E1), Prefix (E2))
8107 and then
8108 FCE (Discrete_Range (E1), Discrete_Range (E2));
8110 when N_String_Literal =>
8111 declare
8112 S1 : constant String_Id := Strval (E1);
8113 S2 : constant String_Id := Strval (E2);
8114 L1 : constant Nat := String_Length (S1);
8115 L2 : constant Nat := String_Length (S2);
8117 begin
8118 if L1 /= L2 then
8119 return False;
8121 else
8122 for J in 1 .. L1 loop
8123 if Get_String_Char (S1, J) /=
8124 Get_String_Char (S2, J)
8125 then
8126 return False;
8127 end if;
8128 end loop;
8130 return True;
8131 end if;
8132 end;
8134 when N_Type_Conversion =>
8135 return
8136 FCE (Subtype_Mark (E1), Subtype_Mark (E2))
8137 and then
8138 FCE (Expression (E1), Expression (E2));
8140 when N_Unary_Op =>
8141 return
8142 Entity (E1) = Entity (E2)
8143 and then
8144 FCE (Right_Opnd (E1), Right_Opnd (E2));
8146 when N_Unchecked_Type_Conversion =>
8147 return
8148 FCE (Subtype_Mark (E1), Subtype_Mark (E2))
8149 and then
8150 FCE (Expression (E1), Expression (E2));
8152 -- All other node types cannot appear in this context. Strictly
8153 -- we should raise a fatal internal error. Instead we just ignore
8154 -- the nodes. This means that if anyone makes a mistake in the
8155 -- expander and mucks an expression tree irretrievably, the result
8156 -- will be a failure to detect a (probably very obscure) case
8157 -- of non-conformance, which is better than bombing on some
8158 -- case where two expressions do in fact conform.
8160 when others =>
8161 return True;
8163 end case;
8164 end if;
8165 end Fully_Conformant_Expressions;
8167 ----------------------------------------
8168 -- Fully_Conformant_Discrete_Subtypes --
8169 ----------------------------------------
8171 function Fully_Conformant_Discrete_Subtypes
8172 (Given_S1 : Node_Id;
8173 Given_S2 : Node_Id) return Boolean
8175 S1 : constant Node_Id := Original_Node (Given_S1);
8176 S2 : constant Node_Id := Original_Node (Given_S2);
8178 function Conforming_Bounds (B1, B2 : Node_Id) return Boolean;
8179 -- Special-case for a bound given by a discriminant, which in the body
8180 -- is replaced with the discriminal of the enclosing type.
8182 function Conforming_Ranges (R1, R2 : Node_Id) return Boolean;
8183 -- Check both bounds
8185 -----------------------
8186 -- Conforming_Bounds --
8187 -----------------------
8189 function Conforming_Bounds (B1, B2 : Node_Id) return Boolean is
8190 begin
8191 if Is_Entity_Name (B1)
8192 and then Is_Entity_Name (B2)
8193 and then Ekind (Entity (B1)) = E_Discriminant
8194 then
8195 return Chars (B1) = Chars (B2);
8197 else
8198 return Fully_Conformant_Expressions (B1, B2);
8199 end if;
8200 end Conforming_Bounds;
8202 -----------------------
8203 -- Conforming_Ranges --
8204 -----------------------
8206 function Conforming_Ranges (R1, R2 : Node_Id) return Boolean is
8207 begin
8208 return
8209 Conforming_Bounds (Low_Bound (R1), Low_Bound (R2))
8210 and then
8211 Conforming_Bounds (High_Bound (R1), High_Bound (R2));
8212 end Conforming_Ranges;
8214 -- Start of processing for Fully_Conformant_Discrete_Subtypes
8216 begin
8217 if Nkind (S1) /= Nkind (S2) then
8218 return False;
8220 elsif Is_Entity_Name (S1) then
8221 return Entity (S1) = Entity (S2);
8223 elsif Nkind (S1) = N_Range then
8224 return Conforming_Ranges (S1, S2);
8226 elsif Nkind (S1) = N_Subtype_Indication then
8227 return
8228 Entity (Subtype_Mark (S1)) = Entity (Subtype_Mark (S2))
8229 and then
8230 Conforming_Ranges
8231 (Range_Expression (Constraint (S1)),
8232 Range_Expression (Constraint (S2)));
8233 else
8234 return True;
8235 end if;
8236 end Fully_Conformant_Discrete_Subtypes;
8238 --------------------
8239 -- Install_Entity --
8240 --------------------
8242 procedure Install_Entity (E : Entity_Id) is
8243 Prev : constant Entity_Id := Current_Entity (E);
8244 begin
8245 Set_Is_Immediately_Visible (E);
8246 Set_Current_Entity (E);
8247 Set_Homonym (E, Prev);
8248 end Install_Entity;
8250 ---------------------
8251 -- Install_Formals --
8252 ---------------------
8254 procedure Install_Formals (Id : Entity_Id) is
8255 F : Entity_Id;
8256 begin
8257 F := First_Formal (Id);
8258 while Present (F) loop
8259 Install_Entity (F);
8260 Next_Formal (F);
8261 end loop;
8262 end Install_Formals;
8264 -----------------------------
8265 -- Is_Interface_Conformant --
8266 -----------------------------
8268 function Is_Interface_Conformant
8269 (Tagged_Type : Entity_Id;
8270 Iface_Prim : Entity_Id;
8271 Prim : Entity_Id) return Boolean
8273 -- The operation may in fact be an inherited (implicit) operation
8274 -- rather than the original interface primitive, so retrieve the
8275 -- ultimate ancestor.
8277 Iface : constant Entity_Id :=
8278 Find_Dispatching_Type (Ultimate_Alias (Iface_Prim));
8279 Typ : constant Entity_Id := Find_Dispatching_Type (Prim);
8281 function Controlling_Formal (Prim : Entity_Id) return Entity_Id;
8282 -- Return the controlling formal of Prim
8284 ------------------------
8285 -- Controlling_Formal --
8286 ------------------------
8288 function Controlling_Formal (Prim : Entity_Id) return Entity_Id is
8289 E : Entity_Id;
8291 begin
8292 E := First_Entity (Prim);
8293 while Present (E) loop
8294 if Is_Formal (E) and then Is_Controlling_Formal (E) then
8295 return E;
8296 end if;
8298 Next_Entity (E);
8299 end loop;
8301 return Empty;
8302 end Controlling_Formal;
8304 -- Local variables
8306 Iface_Ctrl_F : constant Entity_Id := Controlling_Formal (Iface_Prim);
8307 Prim_Ctrl_F : constant Entity_Id := Controlling_Formal (Prim);
8309 -- Start of processing for Is_Interface_Conformant
8311 begin
8312 pragma Assert (Is_Subprogram (Iface_Prim)
8313 and then Is_Subprogram (Prim)
8314 and then Is_Dispatching_Operation (Iface_Prim)
8315 and then Is_Dispatching_Operation (Prim));
8317 pragma Assert (Is_Interface (Iface)
8318 or else (Present (Alias (Iface_Prim))
8319 and then
8320 Is_Interface
8321 (Find_Dispatching_Type (Ultimate_Alias (Iface_Prim)))));
8323 if Prim = Iface_Prim
8324 or else not Is_Subprogram (Prim)
8325 or else Ekind (Prim) /= Ekind (Iface_Prim)
8326 or else not Is_Dispatching_Operation (Prim)
8327 or else Scope (Prim) /= Scope (Tagged_Type)
8328 or else No (Typ)
8329 or else Base_Type (Typ) /= Base_Type (Tagged_Type)
8330 or else not Primitive_Names_Match (Iface_Prim, Prim)
8331 then
8332 return False;
8334 -- The mode of the controlling formals must match
8336 elsif Present (Iface_Ctrl_F)
8337 and then Present (Prim_Ctrl_F)
8338 and then Ekind (Iface_Ctrl_F) /= Ekind (Prim_Ctrl_F)
8339 then
8340 return False;
8342 -- Case of a procedure, or a function whose result type matches the
8343 -- result type of the interface primitive, or a function that has no
8344 -- controlling result (I or access I).
8346 elsif Ekind (Iface_Prim) = E_Procedure
8347 or else Etype (Prim) = Etype (Iface_Prim)
8348 or else not Has_Controlling_Result (Prim)
8349 then
8350 return Type_Conformant
8351 (Iface_Prim, Prim, Skip_Controlling_Formals => True);
8353 -- Case of a function returning an interface, or an access to one. Check
8354 -- that the return types correspond.
8356 elsif Implements_Interface (Typ, Iface) then
8357 if (Ekind (Etype (Prim)) = E_Anonymous_Access_Type)
8359 (Ekind (Etype (Iface_Prim)) = E_Anonymous_Access_Type)
8360 then
8361 return False;
8362 else
8363 return
8364 Type_Conformant (Prim, Ultimate_Alias (Iface_Prim),
8365 Skip_Controlling_Formals => True);
8366 end if;
8368 else
8369 return False;
8370 end if;
8371 end Is_Interface_Conformant;
8373 ---------------------------------
8374 -- Is_Non_Overriding_Operation --
8375 ---------------------------------
8377 function Is_Non_Overriding_Operation
8378 (Prev_E : Entity_Id;
8379 New_E : Entity_Id) return Boolean
8381 Formal : Entity_Id;
8382 F_Typ : Entity_Id;
8383 G_Typ : Entity_Id := Empty;
8385 function Get_Generic_Parent_Type (F_Typ : Entity_Id) return Entity_Id;
8386 -- If F_Type is a derived type associated with a generic actual subtype,
8387 -- then return its Generic_Parent_Type attribute, else return Empty.
8389 function Types_Correspond
8390 (P_Type : Entity_Id;
8391 N_Type : Entity_Id) return Boolean;
8392 -- Returns true if and only if the types (or designated types in the
8393 -- case of anonymous access types) are the same or N_Type is derived
8394 -- directly or indirectly from P_Type.
8396 -----------------------------
8397 -- Get_Generic_Parent_Type --
8398 -----------------------------
8400 function Get_Generic_Parent_Type (F_Typ : Entity_Id) return Entity_Id is
8401 G_Typ : Entity_Id;
8402 Defn : Node_Id;
8403 Indic : Node_Id;
8405 begin
8406 if Is_Derived_Type (F_Typ)
8407 and then Nkind (Parent (F_Typ)) = N_Full_Type_Declaration
8408 then
8409 -- The tree must be traversed to determine the parent subtype in
8410 -- the generic unit, which unfortunately isn't always available
8411 -- via semantic attributes. ??? (Note: The use of Original_Node
8412 -- is needed for cases where a full derived type has been
8413 -- rewritten.)
8415 Defn := Type_Definition (Original_Node (Parent (F_Typ)));
8416 if Nkind (Defn) = N_Derived_Type_Definition then
8417 Indic := Subtype_Indication (Defn);
8419 if Nkind (Indic) = N_Subtype_Indication then
8420 G_Typ := Entity (Subtype_Mark (Indic));
8421 else
8422 G_Typ := Entity (Indic);
8423 end if;
8425 if Nkind (Parent (G_Typ)) = N_Subtype_Declaration
8426 and then Present (Generic_Parent_Type (Parent (G_Typ)))
8427 then
8428 return Generic_Parent_Type (Parent (G_Typ));
8429 end if;
8430 end if;
8431 end if;
8433 return Empty;
8434 end Get_Generic_Parent_Type;
8436 ----------------------
8437 -- Types_Correspond --
8438 ----------------------
8440 function Types_Correspond
8441 (P_Type : Entity_Id;
8442 N_Type : Entity_Id) return Boolean
8444 Prev_Type : Entity_Id := Base_Type (P_Type);
8445 New_Type : Entity_Id := Base_Type (N_Type);
8447 begin
8448 if Ekind (Prev_Type) = E_Anonymous_Access_Type then
8449 Prev_Type := Designated_Type (Prev_Type);
8450 end if;
8452 if Ekind (New_Type) = E_Anonymous_Access_Type then
8453 New_Type := Designated_Type (New_Type);
8454 end if;
8456 if Prev_Type = New_Type then
8457 return True;
8459 elsif not Is_Class_Wide_Type (New_Type) then
8460 while Etype (New_Type) /= New_Type loop
8461 New_Type := Etype (New_Type);
8462 if New_Type = Prev_Type then
8463 return True;
8464 end if;
8465 end loop;
8466 end if;
8467 return False;
8468 end Types_Correspond;
8470 -- Start of processing for Is_Non_Overriding_Operation
8472 begin
8473 -- In the case where both operations are implicit derived subprograms
8474 -- then neither overrides the other. This can only occur in certain
8475 -- obscure cases (e.g., derivation from homographs created in a generic
8476 -- instantiation).
8478 if Present (Alias (Prev_E)) and then Present (Alias (New_E)) then
8479 return True;
8481 elsif Ekind (Current_Scope) = E_Package
8482 and then Is_Generic_Instance (Current_Scope)
8483 and then In_Private_Part (Current_Scope)
8484 and then Comes_From_Source (New_E)
8485 then
8486 -- We examine the formals and result type of the inherited operation,
8487 -- to determine whether their type is derived from (the instance of)
8488 -- a generic type. The first such formal or result type is the one
8489 -- tested.
8491 Formal := First_Formal (Prev_E);
8492 while Present (Formal) loop
8493 F_Typ := Base_Type (Etype (Formal));
8495 if Ekind (F_Typ) = E_Anonymous_Access_Type then
8496 F_Typ := Designated_Type (F_Typ);
8497 end if;
8499 G_Typ := Get_Generic_Parent_Type (F_Typ);
8500 exit when Present (G_Typ);
8502 Next_Formal (Formal);
8503 end loop;
8505 if No (G_Typ) and then Ekind (Prev_E) = E_Function then
8506 G_Typ := Get_Generic_Parent_Type (Base_Type (Etype (Prev_E)));
8507 end if;
8509 if No (G_Typ) then
8510 return False;
8511 end if;
8513 -- If the generic type is a private type, then the original operation
8514 -- was not overriding in the generic, because there was no primitive
8515 -- operation to override.
8517 if Nkind (Parent (G_Typ)) = N_Formal_Type_Declaration
8518 and then Nkind (Formal_Type_Definition (Parent (G_Typ))) =
8519 N_Formal_Private_Type_Definition
8520 then
8521 return True;
8523 -- The generic parent type is the ancestor of a formal derived
8524 -- type declaration. We need to check whether it has a primitive
8525 -- operation that should be overridden by New_E in the generic.
8527 else
8528 declare
8529 P_Formal : Entity_Id;
8530 N_Formal : Entity_Id;
8531 P_Typ : Entity_Id;
8532 N_Typ : Entity_Id;
8533 P_Prim : Entity_Id;
8534 Prim_Elt : Elmt_Id := First_Elmt (Primitive_Operations (G_Typ));
8536 begin
8537 while Present (Prim_Elt) loop
8538 P_Prim := Node (Prim_Elt);
8540 if Chars (P_Prim) = Chars (New_E)
8541 and then Ekind (P_Prim) = Ekind (New_E)
8542 then
8543 P_Formal := First_Formal (P_Prim);
8544 N_Formal := First_Formal (New_E);
8545 while Present (P_Formal) and then Present (N_Formal) loop
8546 P_Typ := Etype (P_Formal);
8547 N_Typ := Etype (N_Formal);
8549 if not Types_Correspond (P_Typ, N_Typ) then
8550 exit;
8551 end if;
8553 Next_Entity (P_Formal);
8554 Next_Entity (N_Formal);
8555 end loop;
8557 -- Found a matching primitive operation belonging to the
8558 -- formal ancestor type, so the new subprogram is
8559 -- overriding.
8561 if No (P_Formal)
8562 and then No (N_Formal)
8563 and then (Ekind (New_E) /= E_Function
8564 or else
8565 Types_Correspond
8566 (Etype (P_Prim), Etype (New_E)))
8567 then
8568 return False;
8569 end if;
8570 end if;
8572 Next_Elmt (Prim_Elt);
8573 end loop;
8575 -- If no match found, then the new subprogram does not override
8576 -- in the generic (nor in the instance).
8578 -- If the type in question is not abstract, and the subprogram
8579 -- is, this will be an error if the new operation is in the
8580 -- private part of the instance. Emit a warning now, which will
8581 -- make the subsequent error message easier to understand.
8583 if not Is_Abstract_Type (F_Typ)
8584 and then Is_Abstract_Subprogram (Prev_E)
8585 and then In_Private_Part (Current_Scope)
8586 then
8587 Error_Msg_Node_2 := F_Typ;
8588 Error_Msg_NE
8589 ("private operation& in generic unit does not override "
8590 & "any primitive operation of& (RM 12.3 (18))??",
8591 New_E, New_E);
8592 end if;
8594 return True;
8595 end;
8596 end if;
8597 else
8598 return False;
8599 end if;
8600 end Is_Non_Overriding_Operation;
8602 -------------------------------------
8603 -- List_Inherited_Pre_Post_Aspects --
8604 -------------------------------------
8606 procedure List_Inherited_Pre_Post_Aspects (E : Entity_Id) is
8607 begin
8608 if Opt.List_Inherited_Aspects
8609 and then Is_Subprogram_Or_Generic_Subprogram (E)
8610 then
8611 declare
8612 Inherited : constant Subprogram_List := Inherited_Subprograms (E);
8613 P : Node_Id;
8615 begin
8616 for J in Inherited'Range loop
8617 P := Pre_Post_Conditions (Contract (Inherited (J)));
8618 while Present (P) loop
8619 Error_Msg_Sloc := Sloc (P);
8621 if Class_Present (P) and then not Split_PPC (P) then
8622 if Pragma_Name (P) = Name_Precondition then
8623 Error_Msg_N ("info: & inherits `Pre''Class` aspect "
8624 & "from #?L?", E);
8625 else
8626 Error_Msg_N ("info: & inherits `Post''Class` aspect "
8627 & "from #?L?", E);
8628 end if;
8629 end if;
8631 P := Next_Pragma (P);
8632 end loop;
8633 end loop;
8634 end;
8635 end if;
8636 end List_Inherited_Pre_Post_Aspects;
8638 ------------------------------
8639 -- Make_Inequality_Operator --
8640 ------------------------------
8642 -- S is the defining identifier of an equality operator. We build a
8643 -- subprogram declaration with the right signature. This operation is
8644 -- intrinsic, because it is always expanded as the negation of the
8645 -- call to the equality function.
8647 procedure Make_Inequality_Operator (S : Entity_Id) is
8648 Loc : constant Source_Ptr := Sloc (S);
8649 Decl : Node_Id;
8650 Formals : List_Id;
8651 Op_Name : Entity_Id;
8653 FF : constant Entity_Id := First_Formal (S);
8654 NF : constant Entity_Id := Next_Formal (FF);
8656 begin
8657 -- Check that equality was properly defined, ignore call if not
8659 if No (NF) then
8660 return;
8661 end if;
8663 declare
8664 A : constant Entity_Id :=
8665 Make_Defining_Identifier (Sloc (FF),
8666 Chars => Chars (FF));
8668 B : constant Entity_Id :=
8669 Make_Defining_Identifier (Sloc (NF),
8670 Chars => Chars (NF));
8672 begin
8673 Op_Name := Make_Defining_Operator_Symbol (Loc, Name_Op_Ne);
8675 Formals := New_List (
8676 Make_Parameter_Specification (Loc,
8677 Defining_Identifier => A,
8678 Parameter_Type =>
8679 New_Occurrence_Of (Etype (First_Formal (S)),
8680 Sloc (Etype (First_Formal (S))))),
8682 Make_Parameter_Specification (Loc,
8683 Defining_Identifier => B,
8684 Parameter_Type =>
8685 New_Occurrence_Of (Etype (Next_Formal (First_Formal (S))),
8686 Sloc (Etype (Next_Formal (First_Formal (S)))))));
8688 Decl :=
8689 Make_Subprogram_Declaration (Loc,
8690 Specification =>
8691 Make_Function_Specification (Loc,
8692 Defining_Unit_Name => Op_Name,
8693 Parameter_Specifications => Formals,
8694 Result_Definition =>
8695 New_Occurrence_Of (Standard_Boolean, Loc)));
8697 -- Insert inequality right after equality if it is explicit or after
8698 -- the derived type when implicit. These entities are created only
8699 -- for visibility purposes, and eventually replaced in the course
8700 -- of expansion, so they do not need to be attached to the tree and
8701 -- seen by the back-end. Keeping them internal also avoids spurious
8702 -- freezing problems. The declaration is inserted in the tree for
8703 -- analysis, and removed afterwards. If the equality operator comes
8704 -- from an explicit declaration, attach the inequality immediately
8705 -- after. Else the equality is inherited from a derived type
8706 -- declaration, so insert inequality after that declaration.
8708 if No (Alias (S)) then
8709 Insert_After (Unit_Declaration_Node (S), Decl);
8710 elsif Is_List_Member (Parent (S)) then
8711 Insert_After (Parent (S), Decl);
8712 else
8713 Insert_After (Parent (Etype (First_Formal (S))), Decl);
8714 end if;
8716 Mark_Rewrite_Insertion (Decl);
8717 Set_Is_Intrinsic_Subprogram (Op_Name);
8718 Analyze (Decl);
8719 Remove (Decl);
8720 Set_Has_Completion (Op_Name);
8721 Set_Corresponding_Equality (Op_Name, S);
8722 Set_Is_Abstract_Subprogram (Op_Name, Is_Abstract_Subprogram (S));
8723 end;
8724 end Make_Inequality_Operator;
8726 ----------------------
8727 -- May_Need_Actuals --
8728 ----------------------
8730 procedure May_Need_Actuals (Fun : Entity_Id) is
8731 F : Entity_Id;
8732 B : Boolean;
8734 begin
8735 F := First_Formal (Fun);
8736 B := True;
8737 while Present (F) loop
8738 if No (Default_Value (F)) then
8739 B := False;
8740 exit;
8741 end if;
8743 Next_Formal (F);
8744 end loop;
8746 Set_Needs_No_Actuals (Fun, B);
8747 end May_Need_Actuals;
8749 ---------------------
8750 -- Mode_Conformant --
8751 ---------------------
8753 function Mode_Conformant (New_Id, Old_Id : Entity_Id) return Boolean is
8754 Result : Boolean;
8755 begin
8756 Check_Conformance (New_Id, Old_Id, Mode_Conformant, False, Result);
8757 return Result;
8758 end Mode_Conformant;
8760 ---------------------------
8761 -- New_Overloaded_Entity --
8762 ---------------------------
8764 procedure New_Overloaded_Entity
8765 (S : Entity_Id;
8766 Derived_Type : Entity_Id := Empty)
8768 Overridden_Subp : Entity_Id := Empty;
8769 -- Set if the current scope has an operation that is type-conformant
8770 -- with S, and becomes hidden by S.
8772 Is_Primitive_Subp : Boolean;
8773 -- Set to True if the new subprogram is primitive
8775 E : Entity_Id;
8776 -- Entity that S overrides
8778 Prev_Vis : Entity_Id := Empty;
8779 -- Predecessor of E in Homonym chain
8781 procedure Check_For_Primitive_Subprogram
8782 (Is_Primitive : out Boolean;
8783 Is_Overriding : Boolean := False);
8784 -- If the subprogram being analyzed is a primitive operation of the type
8785 -- of a formal or result, set the Has_Primitive_Operations flag on the
8786 -- type, and set Is_Primitive to True (otherwise set to False). Set the
8787 -- corresponding flag on the entity itself for later use.
8789 procedure Check_Synchronized_Overriding
8790 (Def_Id : Entity_Id;
8791 Overridden_Subp : out Entity_Id);
8792 -- First determine if Def_Id is an entry or a subprogram either defined
8793 -- in the scope of a task or protected type, or is a primitive of such
8794 -- a type. Check whether Def_Id overrides a subprogram of an interface
8795 -- implemented by the synchronized type, return the overridden entity
8796 -- or Empty.
8798 function Is_Private_Declaration (E : Entity_Id) return Boolean;
8799 -- Check that E is declared in the private part of the current package,
8800 -- or in the package body, where it may hide a previous declaration.
8801 -- We can't use In_Private_Part by itself because this flag is also
8802 -- set when freezing entities, so we must examine the place of the
8803 -- declaration in the tree, and recognize wrapper packages as well.
8805 function Is_Overriding_Alias
8806 (Old_E : Entity_Id;
8807 New_E : Entity_Id) return Boolean;
8808 -- Check whether new subprogram and old subprogram are both inherited
8809 -- from subprograms that have distinct dispatch table entries. This can
8810 -- occur with derivations from instances with accidental homonyms. The
8811 -- function is conservative given that the converse is only true within
8812 -- instances that contain accidental overloadings.
8814 ------------------------------------
8815 -- Check_For_Primitive_Subprogram --
8816 ------------------------------------
8818 procedure Check_For_Primitive_Subprogram
8819 (Is_Primitive : out Boolean;
8820 Is_Overriding : Boolean := False)
8822 Formal : Entity_Id;
8823 F_Typ : Entity_Id;
8824 B_Typ : Entity_Id;
8826 function Visible_Part_Type (T : Entity_Id) return Boolean;
8827 -- Returns true if T is declared in the visible part of the current
8828 -- package scope; otherwise returns false. Assumes that T is declared
8829 -- in a package.
8831 procedure Check_Private_Overriding (T : Entity_Id);
8832 -- Checks that if a primitive abstract subprogram of a visible
8833 -- abstract type is declared in a private part, then it must override
8834 -- an abstract subprogram declared in the visible part. Also checks
8835 -- that if a primitive function with a controlling result is declared
8836 -- in a private part, then it must override a function declared in
8837 -- the visible part.
8839 ------------------------------
8840 -- Check_Private_Overriding --
8841 ------------------------------
8843 procedure Check_Private_Overriding (T : Entity_Id) is
8844 begin
8845 if Is_Package_Or_Generic_Package (Current_Scope)
8846 and then In_Private_Part (Current_Scope)
8847 and then Visible_Part_Type (T)
8848 and then not In_Instance
8849 then
8850 if Is_Abstract_Type (T)
8851 and then Is_Abstract_Subprogram (S)
8852 and then (not Is_Overriding
8853 or else not Is_Abstract_Subprogram (E))
8854 then
8855 Error_Msg_N ("abstract subprograms must be visible "
8856 & "(RM 3.9.3(10))!", S);
8858 elsif Ekind (S) = E_Function and then not Is_Overriding then
8859 if Is_Tagged_Type (T) and then T = Base_Type (Etype (S)) then
8860 Error_Msg_N ("private function with tagged result must"
8861 & " override visible-part function", S);
8862 Error_Msg_N ("\move subprogram to the visible part"
8863 & " (RM 3.9.3(10))", S);
8865 -- AI05-0073: extend this test to the case of a function
8866 -- with a controlling access result.
8868 elsif Ekind (Etype (S)) = E_Anonymous_Access_Type
8869 and then Is_Tagged_Type (Designated_Type (Etype (S)))
8870 and then
8871 not Is_Class_Wide_Type (Designated_Type (Etype (S)))
8872 and then Ada_Version >= Ada_2012
8873 then
8874 Error_Msg_N
8875 ("private function with controlling access result "
8876 & "must override visible-part function", S);
8877 Error_Msg_N
8878 ("\move subprogram to the visible part"
8879 & " (RM 3.9.3(10))", S);
8880 end if;
8881 end if;
8882 end if;
8883 end Check_Private_Overriding;
8885 -----------------------
8886 -- Visible_Part_Type --
8887 -----------------------
8889 function Visible_Part_Type (T : Entity_Id) return Boolean is
8890 P : constant Node_Id := Unit_Declaration_Node (Scope (T));
8891 N : Node_Id;
8893 begin
8894 -- If the entity is a private type, then it must be declared in a
8895 -- visible part.
8897 if Ekind (T) in Private_Kind then
8898 return True;
8899 end if;
8901 -- Otherwise, we traverse the visible part looking for its
8902 -- corresponding declaration. We cannot use the declaration
8903 -- node directly because in the private part the entity of a
8904 -- private type is the one in the full view, which does not
8905 -- indicate that it is the completion of something visible.
8907 N := First (Visible_Declarations (Specification (P)));
8908 while Present (N) loop
8909 if Nkind (N) = N_Full_Type_Declaration
8910 and then Present (Defining_Identifier (N))
8911 and then T = Defining_Identifier (N)
8912 then
8913 return True;
8915 elsif Nkind_In (N, N_Private_Type_Declaration,
8916 N_Private_Extension_Declaration)
8917 and then Present (Defining_Identifier (N))
8918 and then T = Full_View (Defining_Identifier (N))
8919 then
8920 return True;
8921 end if;
8923 Next (N);
8924 end loop;
8926 return False;
8927 end Visible_Part_Type;
8929 -- Start of processing for Check_For_Primitive_Subprogram
8931 begin
8932 Is_Primitive := False;
8934 if not Comes_From_Source (S) then
8935 null;
8937 -- If subprogram is at library level, it is not primitive operation
8939 elsif Current_Scope = Standard_Standard then
8940 null;
8942 elsif (Is_Package_Or_Generic_Package (Current_Scope)
8943 and then not In_Package_Body (Current_Scope))
8944 or else Is_Overriding
8945 then
8946 -- For function, check return type
8948 if Ekind (S) = E_Function then
8949 if Ekind (Etype (S)) = E_Anonymous_Access_Type then
8950 F_Typ := Designated_Type (Etype (S));
8951 else
8952 F_Typ := Etype (S);
8953 end if;
8955 B_Typ := Base_Type (F_Typ);
8957 if Scope (B_Typ) = Current_Scope
8958 and then not Is_Class_Wide_Type (B_Typ)
8959 and then not Is_Generic_Type (B_Typ)
8960 then
8961 Is_Primitive := True;
8962 Set_Has_Primitive_Operations (B_Typ);
8963 Set_Is_Primitive (S);
8964 Check_Private_Overriding (B_Typ);
8965 end if;
8966 end if;
8968 -- For all subprograms, check formals
8970 Formal := First_Formal (S);
8971 while Present (Formal) loop
8972 if Ekind (Etype (Formal)) = E_Anonymous_Access_Type then
8973 F_Typ := Designated_Type (Etype (Formal));
8974 else
8975 F_Typ := Etype (Formal);
8976 end if;
8978 B_Typ := Base_Type (F_Typ);
8980 if Ekind (B_Typ) = E_Access_Subtype then
8981 B_Typ := Base_Type (B_Typ);
8982 end if;
8984 if Scope (B_Typ) = Current_Scope
8985 and then not Is_Class_Wide_Type (B_Typ)
8986 and then not Is_Generic_Type (B_Typ)
8987 then
8988 Is_Primitive := True;
8989 Set_Is_Primitive (S);
8990 Set_Has_Primitive_Operations (B_Typ);
8991 Check_Private_Overriding (B_Typ);
8992 end if;
8994 Next_Formal (Formal);
8995 end loop;
8997 -- Special case: An equality function can be redefined for a type
8998 -- occurring in a declarative part, and won't otherwise be treated as
8999 -- a primitive because it doesn't occur in a package spec and doesn't
9000 -- override an inherited subprogram. It's important that we mark it
9001 -- primitive so it can be returned by Collect_Primitive_Operations
9002 -- and be used in composing the equality operation of later types
9003 -- that have a component of the type.
9005 elsif Chars (S) = Name_Op_Eq
9006 and then Etype (S) = Standard_Boolean
9007 then
9008 B_Typ := Base_Type (Etype (First_Formal (S)));
9010 if Scope (B_Typ) = Current_Scope
9011 and then
9012 Base_Type (Etype (Next_Formal (First_Formal (S)))) = B_Typ
9013 and then not Is_Limited_Type (B_Typ)
9014 then
9015 Is_Primitive := True;
9016 Set_Is_Primitive (S);
9017 Set_Has_Primitive_Operations (B_Typ);
9018 Check_Private_Overriding (B_Typ);
9019 end if;
9020 end if;
9021 end Check_For_Primitive_Subprogram;
9023 -----------------------------------
9024 -- Check_Synchronized_Overriding --
9025 -----------------------------------
9027 procedure Check_Synchronized_Overriding
9028 (Def_Id : Entity_Id;
9029 Overridden_Subp : out Entity_Id)
9031 Ifaces_List : Elist_Id;
9032 In_Scope : Boolean;
9033 Typ : Entity_Id;
9035 function Matches_Prefixed_View_Profile
9036 (Prim_Params : List_Id;
9037 Iface_Params : List_Id) return Boolean;
9038 -- Determine whether a subprogram's parameter profile Prim_Params
9039 -- matches that of a potentially overridden interface subprogram
9040 -- Iface_Params. Also determine if the type of first parameter of
9041 -- Iface_Params is an implemented interface.
9043 -----------------------------------
9044 -- Matches_Prefixed_View_Profile --
9045 -----------------------------------
9047 function Matches_Prefixed_View_Profile
9048 (Prim_Params : List_Id;
9049 Iface_Params : List_Id) return Boolean
9051 Iface_Id : Entity_Id;
9052 Iface_Param : Node_Id;
9053 Iface_Typ : Entity_Id;
9054 Prim_Id : Entity_Id;
9055 Prim_Param : Node_Id;
9056 Prim_Typ : Entity_Id;
9058 function Is_Implemented
9059 (Ifaces_List : Elist_Id;
9060 Iface : Entity_Id) return Boolean;
9061 -- Determine if Iface is implemented by the current task or
9062 -- protected type.
9064 --------------------
9065 -- Is_Implemented --
9066 --------------------
9068 function Is_Implemented
9069 (Ifaces_List : Elist_Id;
9070 Iface : Entity_Id) return Boolean
9072 Iface_Elmt : Elmt_Id;
9074 begin
9075 Iface_Elmt := First_Elmt (Ifaces_List);
9076 while Present (Iface_Elmt) loop
9077 if Node (Iface_Elmt) = Iface then
9078 return True;
9079 end if;
9081 Next_Elmt (Iface_Elmt);
9082 end loop;
9084 return False;
9085 end Is_Implemented;
9087 -- Start of processing for Matches_Prefixed_View_Profile
9089 begin
9090 Iface_Param := First (Iface_Params);
9091 Iface_Typ := Etype (Defining_Identifier (Iface_Param));
9093 if Is_Access_Type (Iface_Typ) then
9094 Iface_Typ := Designated_Type (Iface_Typ);
9095 end if;
9097 Prim_Param := First (Prim_Params);
9099 -- The first parameter of the potentially overridden subprogram
9100 -- must be an interface implemented by Prim.
9102 if not Is_Interface (Iface_Typ)
9103 or else not Is_Implemented (Ifaces_List, Iface_Typ)
9104 then
9105 return False;
9106 end if;
9108 -- The checks on the object parameters are done, move onto the
9109 -- rest of the parameters.
9111 if not In_Scope then
9112 Prim_Param := Next (Prim_Param);
9113 end if;
9115 Iface_Param := Next (Iface_Param);
9116 while Present (Iface_Param) and then Present (Prim_Param) loop
9117 Iface_Id := Defining_Identifier (Iface_Param);
9118 Iface_Typ := Find_Parameter_Type (Iface_Param);
9120 Prim_Id := Defining_Identifier (Prim_Param);
9121 Prim_Typ := Find_Parameter_Type (Prim_Param);
9123 if Ekind (Iface_Typ) = E_Anonymous_Access_Type
9124 and then Ekind (Prim_Typ) = E_Anonymous_Access_Type
9125 and then Is_Concurrent_Type (Designated_Type (Prim_Typ))
9126 then
9127 Iface_Typ := Designated_Type (Iface_Typ);
9128 Prim_Typ := Designated_Type (Prim_Typ);
9129 end if;
9131 -- Case of multiple interface types inside a parameter profile
9133 -- (Obj_Param : in out Iface; ...; Param : Iface)
9135 -- If the interface type is implemented, then the matching type
9136 -- in the primitive should be the implementing record type.
9138 if Ekind (Iface_Typ) = E_Record_Type
9139 and then Is_Interface (Iface_Typ)
9140 and then Is_Implemented (Ifaces_List, Iface_Typ)
9141 then
9142 if Prim_Typ /= Typ then
9143 return False;
9144 end if;
9146 -- The two parameters must be both mode and subtype conformant
9148 elsif Ekind (Iface_Id) /= Ekind (Prim_Id)
9149 or else not
9150 Conforming_Types (Iface_Typ, Prim_Typ, Subtype_Conformant)
9151 then
9152 return False;
9153 end if;
9155 Next (Iface_Param);
9156 Next (Prim_Param);
9157 end loop;
9159 -- One of the two lists contains more parameters than the other
9161 if Present (Iface_Param) or else Present (Prim_Param) then
9162 return False;
9163 end if;
9165 return True;
9166 end Matches_Prefixed_View_Profile;
9168 -- Start of processing for Check_Synchronized_Overriding
9170 begin
9171 Overridden_Subp := Empty;
9173 -- Def_Id must be an entry or a subprogram. We should skip predefined
9174 -- primitives internally generated by the frontend; however at this
9175 -- stage predefined primitives are still not fully decorated. As a
9176 -- minor optimization we skip here internally generated subprograms.
9178 if (Ekind (Def_Id) /= E_Entry
9179 and then Ekind (Def_Id) /= E_Function
9180 and then Ekind (Def_Id) /= E_Procedure)
9181 or else not Comes_From_Source (Def_Id)
9182 then
9183 return;
9184 end if;
9186 -- Search for the concurrent declaration since it contains the list
9187 -- of all implemented interfaces. In this case, the subprogram is
9188 -- declared within the scope of a protected or a task type.
9190 if Present (Scope (Def_Id))
9191 and then Is_Concurrent_Type (Scope (Def_Id))
9192 and then not Is_Generic_Actual_Type (Scope (Def_Id))
9193 then
9194 Typ := Scope (Def_Id);
9195 In_Scope := True;
9197 -- The enclosing scope is not a synchronized type and the subprogram
9198 -- has no formals.
9200 elsif No (First_Formal (Def_Id)) then
9201 return;
9203 -- The subprogram has formals and hence it may be a primitive of a
9204 -- concurrent type.
9206 else
9207 Typ := Etype (First_Formal (Def_Id));
9209 if Is_Access_Type (Typ) then
9210 Typ := Directly_Designated_Type (Typ);
9211 end if;
9213 if Is_Concurrent_Type (Typ)
9214 and then not Is_Generic_Actual_Type (Typ)
9215 then
9216 In_Scope := False;
9218 -- This case occurs when the concurrent type is declared within
9219 -- a generic unit. As a result the corresponding record has been
9220 -- built and used as the type of the first formal, we just have
9221 -- to retrieve the corresponding concurrent type.
9223 elsif Is_Concurrent_Record_Type (Typ)
9224 and then not Is_Class_Wide_Type (Typ)
9225 and then Present (Corresponding_Concurrent_Type (Typ))
9226 then
9227 Typ := Corresponding_Concurrent_Type (Typ);
9228 In_Scope := False;
9230 else
9231 return;
9232 end if;
9233 end if;
9235 -- There is no overriding to check if is an inherited operation in a
9236 -- type derivation on for a generic actual.
9238 Collect_Interfaces (Typ, Ifaces_List);
9240 if Is_Empty_Elmt_List (Ifaces_List) then
9241 return;
9242 end if;
9244 -- Determine whether entry or subprogram Def_Id overrides a primitive
9245 -- operation that belongs to one of the interfaces in Ifaces_List.
9247 declare
9248 Candidate : Entity_Id := Empty;
9249 Hom : Entity_Id := Empty;
9250 Iface_Typ : Entity_Id;
9251 Subp : Entity_Id := Empty;
9253 begin
9254 -- Traverse the homonym chain, looking for a potentially
9255 -- overridden subprogram that belongs to an implemented
9256 -- interface.
9258 Hom := Current_Entity_In_Scope (Def_Id);
9259 while Present (Hom) loop
9260 Subp := Hom;
9262 if Subp = Def_Id
9263 or else not Is_Overloadable (Subp)
9264 or else not Is_Primitive (Subp)
9265 or else not Is_Dispatching_Operation (Subp)
9266 or else not Present (Find_Dispatching_Type (Subp))
9267 or else not Is_Interface (Find_Dispatching_Type (Subp))
9268 then
9269 null;
9271 -- Entries and procedures can override abstract or null
9272 -- interface procedures.
9274 elsif (Ekind (Def_Id) = E_Procedure
9275 or else Ekind (Def_Id) = E_Entry)
9276 and then Ekind (Subp) = E_Procedure
9277 and then Matches_Prefixed_View_Profile
9278 (Parameter_Specifications (Parent (Def_Id)),
9279 Parameter_Specifications (Parent (Subp)))
9280 then
9281 Candidate := Subp;
9283 -- For an overridden subprogram Subp, check whether the mode
9284 -- of its first parameter is correct depending on the kind
9285 -- of synchronized type.
9287 declare
9288 Formal : constant Node_Id := First_Formal (Candidate);
9290 begin
9291 -- In order for an entry or a protected procedure to
9292 -- override, the first parameter of the overridden
9293 -- routine must be of mode "out", "in out" or
9294 -- access-to-variable.
9296 if Ekind_In (Candidate, E_Entry, E_Procedure)
9297 and then Is_Protected_Type (Typ)
9298 and then Ekind (Formal) /= E_In_Out_Parameter
9299 and then Ekind (Formal) /= E_Out_Parameter
9300 and then Nkind (Parameter_Type (Parent (Formal))) /=
9301 N_Access_Definition
9302 then
9303 null;
9305 -- All other cases are OK since a task entry or routine
9306 -- does not have a restriction on the mode of the first
9307 -- parameter of the overridden interface routine.
9309 else
9310 Overridden_Subp := Candidate;
9311 return;
9312 end if;
9313 end;
9315 -- Functions can override abstract interface functions
9317 elsif Ekind (Def_Id) = E_Function
9318 and then Ekind (Subp) = E_Function
9319 and then Matches_Prefixed_View_Profile
9320 (Parameter_Specifications (Parent (Def_Id)),
9321 Parameter_Specifications (Parent (Subp)))
9322 and then Etype (Result_Definition (Parent (Def_Id))) =
9323 Etype (Result_Definition (Parent (Subp)))
9324 then
9325 Overridden_Subp := Subp;
9326 return;
9327 end if;
9329 Hom := Homonym (Hom);
9330 end loop;
9332 -- After examining all candidates for overriding, we are left with
9333 -- the best match which is a mode incompatible interface routine.
9334 -- Do not emit an error if the Expander is active since this error
9335 -- will be detected later on after all concurrent types are
9336 -- expanded and all wrappers are built. This check is meant for
9337 -- spec-only compilations.
9339 if Present (Candidate) and then not Expander_Active then
9340 Iface_Typ :=
9341 Find_Parameter_Type (Parent (First_Formal (Candidate)));
9343 -- Def_Id is primitive of a protected type, declared inside the
9344 -- type, and the candidate is primitive of a limited or
9345 -- synchronized interface.
9347 if In_Scope
9348 and then Is_Protected_Type (Typ)
9349 and then
9350 (Is_Limited_Interface (Iface_Typ)
9351 or else Is_Protected_Interface (Iface_Typ)
9352 or else Is_Synchronized_Interface (Iface_Typ)
9353 or else Is_Task_Interface (Iface_Typ))
9354 then
9355 Error_Msg_PT (Parent (Typ), Candidate);
9356 end if;
9357 end if;
9359 Overridden_Subp := Candidate;
9360 return;
9361 end;
9362 end Check_Synchronized_Overriding;
9364 ----------------------------
9365 -- Is_Private_Declaration --
9366 ----------------------------
9368 function Is_Private_Declaration (E : Entity_Id) return Boolean is
9369 Priv_Decls : List_Id;
9370 Decl : constant Node_Id := Unit_Declaration_Node (E);
9372 begin
9373 if Is_Package_Or_Generic_Package (Current_Scope)
9374 and then In_Private_Part (Current_Scope)
9375 then
9376 Priv_Decls :=
9377 Private_Declarations (Package_Specification (Current_Scope));
9379 return In_Package_Body (Current_Scope)
9380 or else
9381 (Is_List_Member (Decl)
9382 and then List_Containing (Decl) = Priv_Decls)
9383 or else (Nkind (Parent (Decl)) = N_Package_Specification
9384 and then not
9385 Is_Compilation_Unit
9386 (Defining_Entity (Parent (Decl)))
9387 and then List_Containing (Parent (Parent (Decl))) =
9388 Priv_Decls);
9389 else
9390 return False;
9391 end if;
9392 end Is_Private_Declaration;
9394 --------------------------
9395 -- Is_Overriding_Alias --
9396 --------------------------
9398 function Is_Overriding_Alias
9399 (Old_E : Entity_Id;
9400 New_E : Entity_Id) return Boolean
9402 AO : constant Entity_Id := Alias (Old_E);
9403 AN : constant Entity_Id := Alias (New_E);
9404 begin
9405 return Scope (AO) /= Scope (AN)
9406 or else No (DTC_Entity (AO))
9407 or else No (DTC_Entity (AN))
9408 or else DT_Position (AO) = DT_Position (AN);
9409 end Is_Overriding_Alias;
9411 -- Start of processing for New_Overloaded_Entity
9413 begin
9414 -- We need to look for an entity that S may override. This must be a
9415 -- homonym in the current scope, so we look for the first homonym of
9416 -- S in the current scope as the starting point for the search.
9418 E := Current_Entity_In_Scope (S);
9420 -- Ada 2005 (AI-251): Derivation of abstract interface primitives.
9421 -- They are directly added to the list of primitive operations of
9422 -- Derived_Type, unless this is a rederivation in the private part
9423 -- of an operation that was already derived in the visible part of
9424 -- the current package.
9426 if Ada_Version >= Ada_2005
9427 and then Present (Derived_Type)
9428 and then Present (Alias (S))
9429 and then Is_Dispatching_Operation (Alias (S))
9430 and then Present (Find_Dispatching_Type (Alias (S)))
9431 and then Is_Interface (Find_Dispatching_Type (Alias (S)))
9432 then
9433 -- For private types, when the full-view is processed we propagate to
9434 -- the full view the non-overridden entities whose attribute "alias"
9435 -- references an interface primitive. These entities were added by
9436 -- Derive_Subprograms to ensure that interface primitives are
9437 -- covered.
9439 -- Inside_Freeze_Actions is non zero when S corresponds with an
9440 -- internal entity that links an interface primitive with its
9441 -- covering primitive through attribute Interface_Alias (see
9442 -- Add_Internal_Interface_Entities).
9444 if Inside_Freezing_Actions = 0
9445 and then Is_Package_Or_Generic_Package (Current_Scope)
9446 and then In_Private_Part (Current_Scope)
9447 and then Nkind (Parent (E)) = N_Private_Extension_Declaration
9448 and then Nkind (Parent (S)) = N_Full_Type_Declaration
9449 and then Full_View (Defining_Identifier (Parent (E)))
9450 = Defining_Identifier (Parent (S))
9451 and then Alias (E) = Alias (S)
9452 then
9453 Check_Operation_From_Private_View (S, E);
9454 Set_Is_Dispatching_Operation (S);
9456 -- Common case
9458 else
9459 Enter_Overloaded_Entity (S);
9460 Check_Dispatching_Operation (S, Empty);
9461 Check_For_Primitive_Subprogram (Is_Primitive_Subp);
9462 end if;
9464 return;
9465 end if;
9467 -- If there is no homonym then this is definitely not overriding
9469 if No (E) then
9470 Enter_Overloaded_Entity (S);
9471 Check_Dispatching_Operation (S, Empty);
9472 Check_For_Primitive_Subprogram (Is_Primitive_Subp);
9474 -- If subprogram has an explicit declaration, check whether it has an
9475 -- overriding indicator.
9477 if Comes_From_Source (S) then
9478 Check_Synchronized_Overriding (S, Overridden_Subp);
9480 -- (Ada 2012: AI05-0125-1): If S is a dispatching operation then
9481 -- it may have overridden some hidden inherited primitive. Update
9482 -- Overridden_Subp to avoid spurious errors when checking the
9483 -- overriding indicator.
9485 if Ada_Version >= Ada_2012
9486 and then No (Overridden_Subp)
9487 and then Is_Dispatching_Operation (S)
9488 and then Present (Overridden_Operation (S))
9489 then
9490 Overridden_Subp := Overridden_Operation (S);
9491 end if;
9493 Check_Overriding_Indicator
9494 (S, Overridden_Subp, Is_Primitive => Is_Primitive_Subp);
9495 end if;
9497 -- If there is a homonym that is not overloadable, then we have an
9498 -- error, except for the special cases checked explicitly below.
9500 elsif not Is_Overloadable (E) then
9502 -- Check for spurious conflict produced by a subprogram that has the
9503 -- same name as that of the enclosing generic package. The conflict
9504 -- occurs within an instance, between the subprogram and the renaming
9505 -- declaration for the package. After the subprogram, the package
9506 -- renaming declaration becomes hidden.
9508 if Ekind (E) = E_Package
9509 and then Present (Renamed_Object (E))
9510 and then Renamed_Object (E) = Current_Scope
9511 and then Nkind (Parent (Renamed_Object (E))) =
9512 N_Package_Specification
9513 and then Present (Generic_Parent (Parent (Renamed_Object (E))))
9514 then
9515 Set_Is_Hidden (E);
9516 Set_Is_Immediately_Visible (E, False);
9517 Enter_Overloaded_Entity (S);
9518 Set_Homonym (S, Homonym (E));
9519 Check_Dispatching_Operation (S, Empty);
9520 Check_Overriding_Indicator (S, Empty, Is_Primitive => False);
9522 -- If the subprogram is implicit it is hidden by the previous
9523 -- declaration. However if it is dispatching, it must appear in the
9524 -- dispatch table anyway, because it can be dispatched to even if it
9525 -- cannot be called directly.
9527 elsif Present (Alias (S)) and then not Comes_From_Source (S) then
9528 Set_Scope (S, Current_Scope);
9530 if Is_Dispatching_Operation (Alias (S)) then
9531 Check_Dispatching_Operation (S, Empty);
9532 end if;
9534 return;
9536 else
9537 Error_Msg_Sloc := Sloc (E);
9539 -- Generate message, with useful additional warning if in generic
9541 if Is_Generic_Unit (E) then
9542 Error_Msg_N ("previous generic unit cannot be overloaded", S);
9543 Error_Msg_N ("\& conflicts with declaration#", S);
9544 else
9545 Error_Msg_N ("& conflicts with declaration#", S);
9546 end if;
9548 return;
9549 end if;
9551 -- E exists and is overloadable
9553 else
9554 Check_Synchronized_Overriding (S, Overridden_Subp);
9556 -- Loop through E and its homonyms to determine if any of them is
9557 -- the candidate for overriding by S.
9559 while Present (E) loop
9561 -- Definitely not interesting if not in the current scope
9563 if Scope (E) /= Current_Scope then
9564 null;
9566 -- A function can overload the name of an abstract state. The
9567 -- state can be viewed as a function with a profile that cannot
9568 -- be matched by anything.
9570 elsif Ekind (S) = E_Function
9571 and then Ekind (E) = E_Abstract_State
9572 then
9573 Enter_Overloaded_Entity (S);
9574 return;
9576 -- Ada 2012 (AI05-0165): For internally generated bodies of null
9577 -- procedures locate the internally generated spec. We enforce
9578 -- mode conformance since a tagged type may inherit from
9579 -- interfaces several null primitives which differ only in
9580 -- the mode of the formals.
9582 elsif not Comes_From_Source (S)
9583 and then Is_Null_Procedure (S)
9584 and then not Mode_Conformant (E, S)
9585 then
9586 null;
9588 -- Check if we have type conformance
9590 elsif Type_Conformant (E, S) then
9592 -- If the old and new entities have the same profile and one
9593 -- is not the body of the other, then this is an error, unless
9594 -- one of them is implicitly declared.
9596 -- There are some cases when both can be implicit, for example
9597 -- when both a literal and a function that overrides it are
9598 -- inherited in a derivation, or when an inherited operation
9599 -- of a tagged full type overrides the inherited operation of
9600 -- a private extension. Ada 83 had a special rule for the
9601 -- literal case. In Ada 95, the later implicit operation hides
9602 -- the former, and the literal is always the former. In the
9603 -- odd case where both are derived operations declared at the
9604 -- same point, both operations should be declared, and in that
9605 -- case we bypass the following test and proceed to the next
9606 -- part. This can only occur for certain obscure cases in
9607 -- instances, when an operation on a type derived from a formal
9608 -- private type does not override a homograph inherited from
9609 -- the actual. In subsequent derivations of such a type, the
9610 -- DT positions of these operations remain distinct, if they
9611 -- have been set.
9613 if Present (Alias (S))
9614 and then (No (Alias (E))
9615 or else Comes_From_Source (E)
9616 or else Is_Abstract_Subprogram (S)
9617 or else
9618 (Is_Dispatching_Operation (E)
9619 and then Is_Overriding_Alias (E, S)))
9620 and then Ekind (E) /= E_Enumeration_Literal
9621 then
9622 -- When an derived operation is overloaded it may be due to
9623 -- the fact that the full view of a private extension
9624 -- re-inherits. It has to be dealt with.
9626 if Is_Package_Or_Generic_Package (Current_Scope)
9627 and then In_Private_Part (Current_Scope)
9628 then
9629 Check_Operation_From_Private_View (S, E);
9630 end if;
9632 -- In any case the implicit operation remains hidden by the
9633 -- existing declaration, which is overriding. Indicate that
9634 -- E overrides the operation from which S is inherited.
9636 if Present (Alias (S)) then
9637 Set_Overridden_Operation (E, Alias (S));
9638 Inherit_Subprogram_Contract (E, Alias (S));
9640 else
9641 Set_Overridden_Operation (E, S);
9642 Inherit_Subprogram_Contract (E, S);
9643 end if;
9645 if Comes_From_Source (E) then
9646 Check_Overriding_Indicator (E, S, Is_Primitive => False);
9647 end if;
9649 return;
9651 -- Within an instance, the renaming declarations for actual
9652 -- subprograms may become ambiguous, but they do not hide each
9653 -- other.
9655 elsif Ekind (E) /= E_Entry
9656 and then not Comes_From_Source (E)
9657 and then not Is_Generic_Instance (E)
9658 and then (Present (Alias (E))
9659 or else Is_Intrinsic_Subprogram (E))
9660 and then (not In_Instance
9661 or else No (Parent (E))
9662 or else Nkind (Unit_Declaration_Node (E)) /=
9663 N_Subprogram_Renaming_Declaration)
9664 then
9665 -- A subprogram child unit is not allowed to override an
9666 -- inherited subprogram (10.1.1(20)).
9668 if Is_Child_Unit (S) then
9669 Error_Msg_N
9670 ("child unit overrides inherited subprogram in parent",
9672 return;
9673 end if;
9675 if Is_Non_Overriding_Operation (E, S) then
9676 Enter_Overloaded_Entity (S);
9678 if No (Derived_Type)
9679 or else Is_Tagged_Type (Derived_Type)
9680 then
9681 Check_Dispatching_Operation (S, Empty);
9682 end if;
9684 return;
9685 end if;
9687 -- E is a derived operation or an internal operator which
9688 -- is being overridden. Remove E from further visibility.
9689 -- Furthermore, if E is a dispatching operation, it must be
9690 -- replaced in the list of primitive operations of its type
9691 -- (see Override_Dispatching_Operation).
9693 Overridden_Subp := E;
9695 declare
9696 Prev : Entity_Id;
9698 begin
9699 Prev := First_Entity (Current_Scope);
9700 while Present (Prev) and then Next_Entity (Prev) /= E loop
9701 Next_Entity (Prev);
9702 end loop;
9704 -- It is possible for E to be in the current scope and
9705 -- yet not in the entity chain. This can only occur in a
9706 -- generic context where E is an implicit concatenation
9707 -- in the formal part, because in a generic body the
9708 -- entity chain starts with the formals.
9710 -- In GNATprove mode, a wrapper for an operation with
9711 -- axiomatization may be a homonym of another declaration
9712 -- for an actual subprogram (needs refinement ???).
9714 if No (Prev) then
9715 if In_Instance
9716 and then GNATprove_Mode
9717 and then
9718 Nkind (Original_Node (Unit_Declaration_Node (S))) =
9719 N_Subprogram_Renaming_Declaration
9720 then
9721 return;
9722 else
9723 pragma Assert (Chars (E) = Name_Op_Concat);
9724 null;
9725 end if;
9726 end if;
9728 -- E must be removed both from the entity_list of the
9729 -- current scope, and from the visibility chain.
9731 if Debug_Flag_E then
9732 Write_Str ("Override implicit operation ");
9733 Write_Int (Int (E));
9734 Write_Eol;
9735 end if;
9737 -- If E is a predefined concatenation, it stands for four
9738 -- different operations. As a result, a single explicit
9739 -- declaration does not hide it. In a possible ambiguous
9740 -- situation, Disambiguate chooses the user-defined op,
9741 -- so it is correct to retain the previous internal one.
9743 if Chars (E) /= Name_Op_Concat
9744 or else Ekind (E) /= E_Operator
9745 then
9746 -- For nondispatching derived operations that are
9747 -- overridden by a subprogram declared in the private
9748 -- part of a package, we retain the derived subprogram
9749 -- but mark it as not immediately visible. If the
9750 -- derived operation was declared in the visible part
9751 -- then this ensures that it will still be visible
9752 -- outside the package with the proper signature
9753 -- (calls from outside must also be directed to this
9754 -- version rather than the overriding one, unlike the
9755 -- dispatching case). Calls from inside the package
9756 -- will still resolve to the overriding subprogram
9757 -- since the derived one is marked as not visible
9758 -- within the package.
9760 -- If the private operation is dispatching, we achieve
9761 -- the overriding by keeping the implicit operation
9762 -- but setting its alias to be the overriding one. In
9763 -- this fashion the proper body is executed in all
9764 -- cases, but the original signature is used outside
9765 -- of the package.
9767 -- If the overriding is not in the private part, we
9768 -- remove the implicit operation altogether.
9770 if Is_Private_Declaration (S) then
9771 if not Is_Dispatching_Operation (E) then
9772 Set_Is_Immediately_Visible (E, False);
9773 else
9774 -- Work done in Override_Dispatching_Operation,
9775 -- so nothing else needs to be done here.
9777 null;
9778 end if;
9780 else
9781 -- Find predecessor of E in Homonym chain
9783 if E = Current_Entity (E) then
9784 Prev_Vis := Empty;
9785 else
9786 Prev_Vis := Current_Entity (E);
9787 while Homonym (Prev_Vis) /= E loop
9788 Prev_Vis := Homonym (Prev_Vis);
9789 end loop;
9790 end if;
9792 if Prev_Vis /= Empty then
9794 -- Skip E in the visibility chain
9796 Set_Homonym (Prev_Vis, Homonym (E));
9798 else
9799 Set_Name_Entity_Id (Chars (E), Homonym (E));
9800 end if;
9802 Set_Next_Entity (Prev, Next_Entity (E));
9804 if No (Next_Entity (Prev)) then
9805 Set_Last_Entity (Current_Scope, Prev);
9806 end if;
9807 end if;
9808 end if;
9810 Enter_Overloaded_Entity (S);
9812 -- For entities generated by Derive_Subprograms the
9813 -- overridden operation is the inherited primitive
9814 -- (which is available through the attribute alias).
9816 if not (Comes_From_Source (E))
9817 and then Is_Dispatching_Operation (E)
9818 and then Find_Dispatching_Type (E) =
9819 Find_Dispatching_Type (S)
9820 and then Present (Alias (E))
9821 and then Comes_From_Source (Alias (E))
9822 then
9823 Set_Overridden_Operation (S, Alias (E));
9824 Inherit_Subprogram_Contract (S, Alias (E));
9826 -- Normal case of setting entity as overridden
9828 -- Note: Static_Initialization and Overridden_Operation
9829 -- attributes use the same field in subprogram entities.
9830 -- Static_Initialization is only defined for internal
9831 -- initialization procedures, where Overridden_Operation
9832 -- is irrelevant. Therefore the setting of this attribute
9833 -- must check whether the target is an init_proc.
9835 elsif not Is_Init_Proc (S) then
9836 Set_Overridden_Operation (S, E);
9837 Inherit_Subprogram_Contract (S, E);
9838 end if;
9840 Check_Overriding_Indicator (S, E, Is_Primitive => True);
9842 -- If S is a user-defined subprogram or a null procedure
9843 -- expanded to override an inherited null procedure, or a
9844 -- predefined dispatching primitive then indicate that E
9845 -- overrides the operation from which S is inherited.
9847 if Comes_From_Source (S)
9848 or else
9849 (Present (Parent (S))
9850 and then
9851 Nkind (Parent (S)) = N_Procedure_Specification
9852 and then
9853 Null_Present (Parent (S)))
9854 or else
9855 (Present (Alias (E))
9856 and then
9857 Is_Predefined_Dispatching_Operation (Alias (E)))
9858 then
9859 if Present (Alias (E)) then
9860 Set_Overridden_Operation (S, Alias (E));
9861 Inherit_Subprogram_Contract (S, Alias (E));
9862 end if;
9863 end if;
9865 if Is_Dispatching_Operation (E) then
9867 -- An overriding dispatching subprogram inherits the
9868 -- convention of the overridden subprogram (AI-117).
9870 Set_Convention (S, Convention (E));
9871 Check_Dispatching_Operation (S, E);
9873 else
9874 Check_Dispatching_Operation (S, Empty);
9875 end if;
9877 Check_For_Primitive_Subprogram
9878 (Is_Primitive_Subp, Is_Overriding => True);
9879 goto Check_Inequality;
9880 end;
9882 -- Apparent redeclarations in instances can occur when two
9883 -- formal types get the same actual type. The subprograms in
9884 -- in the instance are legal, even if not callable from the
9885 -- outside. Calls from within are disambiguated elsewhere.
9886 -- For dispatching operations in the visible part, the usual
9887 -- rules apply, and operations with the same profile are not
9888 -- legal (B830001).
9890 elsif (In_Instance_Visible_Part
9891 and then not Is_Dispatching_Operation (E))
9892 or else In_Instance_Not_Visible
9893 then
9894 null;
9896 -- Here we have a real error (identical profile)
9898 else
9899 Error_Msg_Sloc := Sloc (E);
9901 -- Avoid cascaded errors if the entity appears in
9902 -- subsequent calls.
9904 Set_Scope (S, Current_Scope);
9906 -- Generate error, with extra useful warning for the case
9907 -- of a generic instance with no completion.
9909 if Is_Generic_Instance (S)
9910 and then not Has_Completion (E)
9911 then
9912 Error_Msg_N
9913 ("instantiation cannot provide body for&", S);
9914 Error_Msg_N ("\& conflicts with declaration#", S);
9915 else
9916 Error_Msg_N ("& conflicts with declaration#", S);
9917 end if;
9919 return;
9920 end if;
9922 else
9923 -- If one subprogram has an access parameter and the other
9924 -- a parameter of an access type, calls to either might be
9925 -- ambiguous. Verify that parameters match except for the
9926 -- access parameter.
9928 if May_Hide_Profile then
9929 declare
9930 F1 : Entity_Id;
9931 F2 : Entity_Id;
9933 begin
9934 F1 := First_Formal (S);
9935 F2 := First_Formal (E);
9936 while Present (F1) and then Present (F2) loop
9937 if Is_Access_Type (Etype (F1)) then
9938 if not Is_Access_Type (Etype (F2))
9939 or else not Conforming_Types
9940 (Designated_Type (Etype (F1)),
9941 Designated_Type (Etype (F2)),
9942 Type_Conformant)
9943 then
9944 May_Hide_Profile := False;
9945 end if;
9947 elsif
9948 not Conforming_Types
9949 (Etype (F1), Etype (F2), Type_Conformant)
9950 then
9951 May_Hide_Profile := False;
9952 end if;
9954 Next_Formal (F1);
9955 Next_Formal (F2);
9956 end loop;
9958 if May_Hide_Profile
9959 and then No (F1)
9960 and then No (F2)
9961 then
9962 Error_Msg_NE ("calls to& may be ambiguous??", S, S);
9963 end if;
9964 end;
9965 end if;
9966 end if;
9968 E := Homonym (E);
9969 end loop;
9971 -- On exit, we know that S is a new entity
9973 Enter_Overloaded_Entity (S);
9974 Check_For_Primitive_Subprogram (Is_Primitive_Subp);
9975 Check_Overriding_Indicator
9976 (S, Overridden_Subp, Is_Primitive => Is_Primitive_Subp);
9978 -- Overloading is not allowed in SPARK, except for operators
9980 if Nkind (S) /= N_Defining_Operator_Symbol then
9981 Error_Msg_Sloc := Sloc (Homonym (S));
9982 Check_SPARK_05_Restriction
9983 ("overloading not allowed with entity#", S);
9984 end if;
9986 -- If S is a derived operation for an untagged type then by
9987 -- definition it's not a dispatching operation (even if the parent
9988 -- operation was dispatching), so Check_Dispatching_Operation is not
9989 -- called in that case.
9991 if No (Derived_Type)
9992 or else Is_Tagged_Type (Derived_Type)
9993 then
9994 Check_Dispatching_Operation (S, Empty);
9995 end if;
9996 end if;
9998 -- If this is a user-defined equality operator that is not a derived
9999 -- subprogram, create the corresponding inequality. If the operation is
10000 -- dispatching, the expansion is done elsewhere, and we do not create
10001 -- an explicit inequality operation.
10003 <<Check_Inequality>>
10004 if Chars (S) = Name_Op_Eq
10005 and then Etype (S) = Standard_Boolean
10006 and then Present (Parent (S))
10007 and then not Is_Dispatching_Operation (S)
10008 then
10009 Make_Inequality_Operator (S);
10010 Check_Untagged_Equality (S);
10011 end if;
10012 end New_Overloaded_Entity;
10014 ---------------------
10015 -- Process_Formals --
10016 ---------------------
10018 procedure Process_Formals
10019 (T : List_Id;
10020 Related_Nod : Node_Id)
10022 Param_Spec : Node_Id;
10023 Formal : Entity_Id;
10024 Formal_Type : Entity_Id;
10025 Default : Node_Id;
10026 Ptype : Entity_Id;
10028 Num_Out_Params : Nat := 0;
10029 First_Out_Param : Entity_Id := Empty;
10030 -- Used for setting Is_Only_Out_Parameter
10032 function Designates_From_Limited_With (Typ : Entity_Id) return Boolean;
10033 -- Determine whether an access type designates a type coming from a
10034 -- limited view.
10036 function Is_Class_Wide_Default (D : Node_Id) return Boolean;
10037 -- Check whether the default has a class-wide type. After analysis the
10038 -- default has the type of the formal, so we must also check explicitly
10039 -- for an access attribute.
10041 ----------------------------------
10042 -- Designates_From_Limited_With --
10043 ----------------------------------
10045 function Designates_From_Limited_With (Typ : Entity_Id) return Boolean is
10046 Desig : Entity_Id := Typ;
10048 begin
10049 if Is_Access_Type (Desig) then
10050 Desig := Directly_Designated_Type (Desig);
10051 end if;
10053 if Is_Class_Wide_Type (Desig) then
10054 Desig := Root_Type (Desig);
10055 end if;
10057 return
10058 Ekind (Desig) = E_Incomplete_Type
10059 and then From_Limited_With (Desig);
10060 end Designates_From_Limited_With;
10062 ---------------------------
10063 -- Is_Class_Wide_Default --
10064 ---------------------------
10066 function Is_Class_Wide_Default (D : Node_Id) return Boolean is
10067 begin
10068 return Is_Class_Wide_Type (Designated_Type (Etype (D)))
10069 or else (Nkind (D) = N_Attribute_Reference
10070 and then Attribute_Name (D) = Name_Access
10071 and then Is_Class_Wide_Type (Etype (Prefix (D))));
10072 end Is_Class_Wide_Default;
10074 -- Start of processing for Process_Formals
10076 begin
10077 -- In order to prevent premature use of the formals in the same formal
10078 -- part, the Ekind is left undefined until all default expressions are
10079 -- analyzed. The Ekind is established in a separate loop at the end.
10081 Param_Spec := First (T);
10082 while Present (Param_Spec) loop
10083 Formal := Defining_Identifier (Param_Spec);
10084 Set_Never_Set_In_Source (Formal, True);
10085 Enter_Name (Formal);
10087 -- Case of ordinary parameters
10089 if Nkind (Parameter_Type (Param_Spec)) /= N_Access_Definition then
10090 Find_Type (Parameter_Type (Param_Spec));
10091 Ptype := Parameter_Type (Param_Spec);
10093 if Ptype = Error then
10094 goto Continue;
10095 end if;
10097 Formal_Type := Entity (Ptype);
10099 if Is_Incomplete_Type (Formal_Type)
10100 or else
10101 (Is_Class_Wide_Type (Formal_Type)
10102 and then Is_Incomplete_Type (Root_Type (Formal_Type)))
10103 then
10104 -- Ada 2005 (AI-326): Tagged incomplete types allowed in
10105 -- primitive operations, as long as their completion is
10106 -- in the same declarative part. If in the private part
10107 -- this means that the type cannot be a Taft-amendment type.
10108 -- Check is done on package exit. For access to subprograms,
10109 -- the use is legal for Taft-amendment types.
10111 -- Ada 2012: tagged incomplete types are allowed as generic
10112 -- formal types. They do not introduce dependencies and the
10113 -- corresponding generic subprogram does not have a delayed
10114 -- freeze, because it does not need a freeze node. However,
10115 -- it is still the case that untagged incomplete types cannot
10116 -- be Taft-amendment types and must be completed in private
10117 -- part, so the subprogram must appear in the list of private
10118 -- dependents of the type.
10120 if Is_Tagged_Type (Formal_Type)
10121 or else (Ada_Version >= Ada_2012
10122 and then not From_Limited_With (Formal_Type)
10123 and then not Is_Generic_Type (Formal_Type))
10124 then
10125 if Ekind (Scope (Current_Scope)) = E_Package
10126 and then not Is_Generic_Type (Formal_Type)
10127 and then not Is_Class_Wide_Type (Formal_Type)
10128 then
10129 if not Nkind_In
10130 (Parent (T), N_Access_Function_Definition,
10131 N_Access_Procedure_Definition)
10132 then
10133 Append_Elmt
10134 (Current_Scope,
10135 To => Private_Dependents (Base_Type (Formal_Type)));
10137 -- Freezing is delayed to ensure that Register_Prim
10138 -- will get called for this operation, which is needed
10139 -- in cases where static dispatch tables aren't built.
10140 -- (Note that the same is done for controlling access
10141 -- parameter cases in function Access_Definition.)
10143 if not Is_Thunk (Current_Scope) then
10144 Set_Has_Delayed_Freeze (Current_Scope);
10145 end if;
10146 end if;
10147 end if;
10149 -- Special handling of Value_Type for CIL case
10151 elsif Is_Value_Type (Formal_Type) then
10152 null;
10154 elsif not Nkind_In (Parent (T), N_Access_Function_Definition,
10155 N_Access_Procedure_Definition)
10156 then
10157 -- AI05-0151: Tagged incomplete types are allowed in all
10158 -- formal parts. Untagged incomplete types are not allowed
10159 -- in bodies. Limited views of either kind are not allowed
10160 -- if there is no place at which the non-limited view can
10161 -- become available.
10163 -- Incomplete formal untagged types are not allowed in
10164 -- subprogram bodies (but are legal in their declarations).
10166 if Is_Generic_Type (Formal_Type)
10167 and then not Is_Tagged_Type (Formal_Type)
10168 and then Nkind (Parent (Related_Nod)) = N_Subprogram_Body
10169 then
10170 Error_Msg_N
10171 ("invalid use of formal incomplete type", Param_Spec);
10173 elsif Ada_Version >= Ada_2012 then
10174 if Is_Tagged_Type (Formal_Type)
10175 and then (not From_Limited_With (Formal_Type)
10176 or else not In_Package_Body)
10177 then
10178 null;
10180 elsif Nkind_In (Parent (Parent (T)), N_Accept_Statement,
10181 N_Accept_Alternative,
10182 N_Entry_Body,
10183 N_Subprogram_Body)
10184 then
10185 Error_Msg_NE
10186 ("invalid use of untagged incomplete type&",
10187 Ptype, Formal_Type);
10188 end if;
10190 else
10191 Error_Msg_NE
10192 ("invalid use of incomplete type&",
10193 Param_Spec, Formal_Type);
10195 -- Further checks on the legality of incomplete types
10196 -- in formal parts are delayed until the freeze point
10197 -- of the enclosing subprogram or access to subprogram.
10198 end if;
10199 end if;
10201 elsif Ekind (Formal_Type) = E_Void then
10202 Error_Msg_NE
10203 ("premature use of&",
10204 Parameter_Type (Param_Spec), Formal_Type);
10205 end if;
10207 -- Ada 2012 (AI-142): Handle aliased parameters
10209 if Ada_Version >= Ada_2012
10210 and then Aliased_Present (Param_Spec)
10211 then
10212 Set_Is_Aliased (Formal);
10213 end if;
10215 -- Ada 2005 (AI-231): Create and decorate an internal subtype
10216 -- declaration corresponding to the null-excluding type of the
10217 -- formal in the enclosing scope. Finally, replace the parameter
10218 -- type of the formal with the internal subtype.
10220 if Ada_Version >= Ada_2005
10221 and then Null_Exclusion_Present (Param_Spec)
10222 then
10223 if not Is_Access_Type (Formal_Type) then
10224 Error_Msg_N
10225 ("`NOT NULL` allowed only for an access type", Param_Spec);
10227 else
10228 if Can_Never_Be_Null (Formal_Type)
10229 and then Comes_From_Source (Related_Nod)
10230 then
10231 Error_Msg_NE
10232 ("`NOT NULL` not allowed (& already excludes null)",
10233 Param_Spec, Formal_Type);
10234 end if;
10236 Formal_Type :=
10237 Create_Null_Excluding_Itype
10238 (T => Formal_Type,
10239 Related_Nod => Related_Nod,
10240 Scope_Id => Scope (Current_Scope));
10242 -- If the designated type of the itype is an itype that is
10243 -- not frozen yet, we set the Has_Delayed_Freeze attribute
10244 -- on the access subtype, to prevent order-of-elaboration
10245 -- issues in the backend.
10247 -- Example:
10248 -- type T is access procedure;
10249 -- procedure Op (O : not null T);
10251 if Is_Itype (Directly_Designated_Type (Formal_Type))
10252 and then
10253 not Is_Frozen (Directly_Designated_Type (Formal_Type))
10254 then
10255 Set_Has_Delayed_Freeze (Formal_Type);
10256 end if;
10257 end if;
10258 end if;
10260 -- An access formal type
10262 else
10263 Formal_Type :=
10264 Access_Definition (Related_Nod, Parameter_Type (Param_Spec));
10266 -- No need to continue if we already notified errors
10268 if not Present (Formal_Type) then
10269 return;
10270 end if;
10272 -- Ada 2005 (AI-254)
10274 declare
10275 AD : constant Node_Id :=
10276 Access_To_Subprogram_Definition
10277 (Parameter_Type (Param_Spec));
10278 begin
10279 if Present (AD) and then Protected_Present (AD) then
10280 Formal_Type :=
10281 Replace_Anonymous_Access_To_Protected_Subprogram
10282 (Param_Spec);
10283 end if;
10284 end;
10285 end if;
10287 Set_Etype (Formal, Formal_Type);
10289 -- Deal with default expression if present
10291 Default := Expression (Param_Spec);
10293 if Present (Default) then
10294 Check_SPARK_05_Restriction
10295 ("default expression is not allowed", Default);
10297 if Out_Present (Param_Spec) then
10298 Error_Msg_N
10299 ("default initialization only allowed for IN parameters",
10300 Param_Spec);
10301 end if;
10303 -- Do the special preanalysis of the expression (see section on
10304 -- "Handling of Default Expressions" in the spec of package Sem).
10306 Preanalyze_Spec_Expression (Default, Formal_Type);
10308 -- An access to constant cannot be the default for
10309 -- an access parameter that is an access to variable.
10311 if Ekind (Formal_Type) = E_Anonymous_Access_Type
10312 and then not Is_Access_Constant (Formal_Type)
10313 and then Is_Access_Type (Etype (Default))
10314 and then Is_Access_Constant (Etype (Default))
10315 then
10316 Error_Msg_N
10317 ("formal that is access to variable cannot be initialized "
10318 & "with an access-to-constant expression", Default);
10319 end if;
10321 -- Check that the designated type of an access parameter's default
10322 -- is not a class-wide type unless the parameter's designated type
10323 -- is also class-wide.
10325 if Ekind (Formal_Type) = E_Anonymous_Access_Type
10326 and then not Designates_From_Limited_With (Formal_Type)
10327 and then Is_Class_Wide_Default (Default)
10328 and then not Is_Class_Wide_Type (Designated_Type (Formal_Type))
10329 then
10330 Error_Msg_N
10331 ("access to class-wide expression not allowed here", Default);
10332 end if;
10334 -- Check incorrect use of dynamically tagged expressions
10336 if Is_Tagged_Type (Formal_Type) then
10337 Check_Dynamically_Tagged_Expression
10338 (Expr => Default,
10339 Typ => Formal_Type,
10340 Related_Nod => Default);
10341 end if;
10342 end if;
10344 -- Ada 2005 (AI-231): Static checks
10346 if Ada_Version >= Ada_2005
10347 and then Is_Access_Type (Etype (Formal))
10348 and then Can_Never_Be_Null (Etype (Formal))
10349 then
10350 Null_Exclusion_Static_Checks (Param_Spec);
10351 end if;
10353 -- The following checks are relevant when SPARK_Mode is on as these
10354 -- are not standard Ada legality rules.
10356 if SPARK_Mode = On then
10357 if Ekind_In (Scope (Formal), E_Function, E_Generic_Function) then
10359 -- A function cannot have a parameter of mode IN OUT or OUT
10360 -- (SPARK RM 6.1).
10362 if Ekind_In (Formal, E_In_Out_Parameter, E_Out_Parameter) then
10363 Error_Msg_N
10364 ("function cannot have parameter of mode `OUT` or "
10365 & "`IN OUT`", Formal);
10367 -- A function cannot have an effectively volatile formal
10368 -- parameter (SPARK RM 7.1.3(10)).
10370 elsif Is_Effectively_Volatile (Formal) then
10371 Error_Msg_N
10372 ("function cannot have a volatile formal parameter",
10373 Formal);
10374 end if;
10376 -- A procedure cannot have an effectively volatile formal
10377 -- parameter of mode IN because it behaves as a constant
10378 -- (SPARK RM 7.1.3(6)).
10380 elsif Ekind (Scope (Formal)) = E_Procedure
10381 and then Ekind (Formal) = E_In_Parameter
10382 and then Is_Effectively_Volatile (Formal)
10383 then
10384 Error_Msg_N
10385 ("formal parameter of mode `IN` cannot be volatile", Formal);
10386 end if;
10387 end if;
10389 <<Continue>>
10390 Next (Param_Spec);
10391 end loop;
10393 -- If this is the formal part of a function specification, analyze the
10394 -- subtype mark in the context where the formals are visible but not
10395 -- yet usable, and may hide outer homographs.
10397 if Nkind (Related_Nod) = N_Function_Specification then
10398 Analyze_Return_Type (Related_Nod);
10399 end if;
10401 -- Now set the kind (mode) of each formal
10403 Param_Spec := First (T);
10404 while Present (Param_Spec) loop
10405 Formal := Defining_Identifier (Param_Spec);
10406 Set_Formal_Mode (Formal);
10408 if Ekind (Formal) = E_In_Parameter then
10409 Set_Default_Value (Formal, Expression (Param_Spec));
10411 if Present (Expression (Param_Spec)) then
10412 Default := Expression (Param_Spec);
10414 if Is_Scalar_Type (Etype (Default)) then
10415 if Nkind (Parameter_Type (Param_Spec)) /=
10416 N_Access_Definition
10417 then
10418 Formal_Type := Entity (Parameter_Type (Param_Spec));
10419 else
10420 Formal_Type :=
10421 Access_Definition
10422 (Related_Nod, Parameter_Type (Param_Spec));
10423 end if;
10425 Apply_Scalar_Range_Check (Default, Formal_Type);
10426 end if;
10427 end if;
10429 elsif Ekind (Formal) = E_Out_Parameter then
10430 Num_Out_Params := Num_Out_Params + 1;
10432 if Num_Out_Params = 1 then
10433 First_Out_Param := Formal;
10434 end if;
10436 elsif Ekind (Formal) = E_In_Out_Parameter then
10437 Num_Out_Params := Num_Out_Params + 1;
10438 end if;
10440 -- Skip remaining processing if formal type was in error
10442 if Etype (Formal) = Any_Type or else Error_Posted (Formal) then
10443 goto Next_Parameter;
10444 end if;
10446 -- Force call by reference if aliased
10448 if Is_Aliased (Formal) then
10449 Set_Mechanism (Formal, By_Reference);
10451 -- Warn if user asked this to be passed by copy
10453 if Convention (Formal_Type) = Convention_Ada_Pass_By_Copy then
10454 Error_Msg_N
10455 ("cannot pass aliased parameter & by copy??", Formal);
10456 end if;
10458 -- Force mechanism if type has Convention Ada_Pass_By_Ref/Copy
10460 elsif Convention (Formal_Type) = Convention_Ada_Pass_By_Copy then
10461 Set_Mechanism (Formal, By_Copy);
10463 elsif Convention (Formal_Type) = Convention_Ada_Pass_By_Reference then
10464 Set_Mechanism (Formal, By_Reference);
10465 end if;
10467 <<Next_Parameter>>
10468 Next (Param_Spec);
10469 end loop;
10471 if Present (First_Out_Param) and then Num_Out_Params = 1 then
10472 Set_Is_Only_Out_Parameter (First_Out_Param);
10473 end if;
10474 end Process_Formals;
10476 ----------------------------
10477 -- Reference_Body_Formals --
10478 ----------------------------
10480 procedure Reference_Body_Formals (Spec : Entity_Id; Bod : Entity_Id) is
10481 Fs : Entity_Id;
10482 Fb : Entity_Id;
10484 begin
10485 if Error_Posted (Spec) then
10486 return;
10487 end if;
10489 -- Iterate over both lists. They may be of different lengths if the two
10490 -- specs are not conformant.
10492 Fs := First_Formal (Spec);
10493 Fb := First_Formal (Bod);
10494 while Present (Fs) and then Present (Fb) loop
10495 Generate_Reference (Fs, Fb, 'b');
10497 if Style_Check then
10498 Style.Check_Identifier (Fb, Fs);
10499 end if;
10501 Set_Spec_Entity (Fb, Fs);
10502 Set_Referenced (Fs, False);
10503 Next_Formal (Fs);
10504 Next_Formal (Fb);
10505 end loop;
10506 end Reference_Body_Formals;
10508 -------------------------
10509 -- Set_Actual_Subtypes --
10510 -------------------------
10512 procedure Set_Actual_Subtypes (N : Node_Id; Subp : Entity_Id) is
10513 Decl : Node_Id;
10514 Formal : Entity_Id;
10515 T : Entity_Id;
10516 First_Stmt : Node_Id := Empty;
10517 AS_Needed : Boolean;
10519 begin
10520 -- If this is an empty initialization procedure, no need to create
10521 -- actual subtypes (small optimization).
10523 if Ekind (Subp) = E_Procedure and then Is_Null_Init_Proc (Subp) then
10524 return;
10525 end if;
10527 Formal := First_Formal (Subp);
10528 while Present (Formal) loop
10529 T := Etype (Formal);
10531 -- We never need an actual subtype for a constrained formal
10533 if Is_Constrained (T) then
10534 AS_Needed := False;
10536 -- If we have unknown discriminants, then we do not need an actual
10537 -- subtype, or more accurately we cannot figure it out. Note that
10538 -- all class-wide types have unknown discriminants.
10540 elsif Has_Unknown_Discriminants (T) then
10541 AS_Needed := False;
10543 -- At this stage we have an unconstrained type that may need an
10544 -- actual subtype. For sure the actual subtype is needed if we have
10545 -- an unconstrained array type.
10547 elsif Is_Array_Type (T) then
10548 AS_Needed := True;
10550 -- The only other case needing an actual subtype is an unconstrained
10551 -- record type which is an IN parameter (we cannot generate actual
10552 -- subtypes for the OUT or IN OUT case, since an assignment can
10553 -- change the discriminant values. However we exclude the case of
10554 -- initialization procedures, since discriminants are handled very
10555 -- specially in this context, see the section entitled "Handling of
10556 -- Discriminants" in Einfo.
10558 -- We also exclude the case of Discrim_SO_Functions (functions used
10559 -- in front end layout mode for size/offset values), since in such
10560 -- functions only discriminants are referenced, and not only are such
10561 -- subtypes not needed, but they cannot always be generated, because
10562 -- of order of elaboration issues.
10564 elsif Is_Record_Type (T)
10565 and then Ekind (Formal) = E_In_Parameter
10566 and then Chars (Formal) /= Name_uInit
10567 and then not Is_Unchecked_Union (T)
10568 and then not Is_Discrim_SO_Function (Subp)
10569 then
10570 AS_Needed := True;
10572 -- All other cases do not need an actual subtype
10574 else
10575 AS_Needed := False;
10576 end if;
10578 -- Generate actual subtypes for unconstrained arrays and
10579 -- unconstrained discriminated records.
10581 if AS_Needed then
10582 if Nkind (N) = N_Accept_Statement then
10584 -- If expansion is active, the formal is replaced by a local
10585 -- variable that renames the corresponding entry of the
10586 -- parameter block, and it is this local variable that may
10587 -- require an actual subtype.
10589 if Expander_Active then
10590 Decl := Build_Actual_Subtype (T, Renamed_Object (Formal));
10591 else
10592 Decl := Build_Actual_Subtype (T, Formal);
10593 end if;
10595 if Present (Handled_Statement_Sequence (N)) then
10596 First_Stmt :=
10597 First (Statements (Handled_Statement_Sequence (N)));
10598 Prepend (Decl, Statements (Handled_Statement_Sequence (N)));
10599 Mark_Rewrite_Insertion (Decl);
10600 else
10601 -- If the accept statement has no body, there will be no
10602 -- reference to the actuals, so no need to compute actual
10603 -- subtypes.
10605 return;
10606 end if;
10608 else
10609 Decl := Build_Actual_Subtype (T, Formal);
10610 Prepend (Decl, Declarations (N));
10611 Mark_Rewrite_Insertion (Decl);
10612 end if;
10614 -- The declaration uses the bounds of an existing object, and
10615 -- therefore needs no constraint checks.
10617 Analyze (Decl, Suppress => All_Checks);
10619 -- We need to freeze manually the generated type when it is
10620 -- inserted anywhere else than in a declarative part.
10622 if Present (First_Stmt) then
10623 Insert_List_Before_And_Analyze (First_Stmt,
10624 Freeze_Entity (Defining_Identifier (Decl), N));
10626 -- Ditto if the type has a dynamic predicate, because the
10627 -- generated function will mention the actual subtype.
10629 elsif Has_Dynamic_Predicate_Aspect (T) then
10630 Insert_List_Before_And_Analyze (Decl,
10631 Freeze_Entity (Defining_Identifier (Decl), N));
10632 end if;
10634 if Nkind (N) = N_Accept_Statement
10635 and then Expander_Active
10636 then
10637 Set_Actual_Subtype (Renamed_Object (Formal),
10638 Defining_Identifier (Decl));
10639 else
10640 Set_Actual_Subtype (Formal, Defining_Identifier (Decl));
10641 end if;
10642 end if;
10644 Next_Formal (Formal);
10645 end loop;
10646 end Set_Actual_Subtypes;
10648 ---------------------
10649 -- Set_Formal_Mode --
10650 ---------------------
10652 procedure Set_Formal_Mode (Formal_Id : Entity_Id) is
10653 Spec : constant Node_Id := Parent (Formal_Id);
10655 begin
10656 -- Note: we set Is_Known_Valid for IN parameters and IN OUT parameters
10657 -- since we ensure that corresponding actuals are always valid at the
10658 -- point of the call.
10660 if Out_Present (Spec) then
10661 if Ekind_In (Scope (Formal_Id), E_Function, E_Generic_Function) then
10663 -- [IN] OUT parameters allowed for functions in Ada 2012
10665 if Ada_Version >= Ada_2012 then
10667 -- Even in Ada 2012 operators can only have IN parameters
10669 if Is_Operator_Symbol_Name (Chars (Scope (Formal_Id))) then
10670 Error_Msg_N ("operators can only have IN parameters", Spec);
10671 end if;
10673 if In_Present (Spec) then
10674 Set_Ekind (Formal_Id, E_In_Out_Parameter);
10675 else
10676 Set_Ekind (Formal_Id, E_Out_Parameter);
10677 end if;
10679 Set_Has_Out_Or_In_Out_Parameter (Scope (Formal_Id), True);
10681 -- But not in earlier versions of Ada
10683 else
10684 Error_Msg_N ("functions can only have IN parameters", Spec);
10685 Set_Ekind (Formal_Id, E_In_Parameter);
10686 end if;
10688 elsif In_Present (Spec) then
10689 Set_Ekind (Formal_Id, E_In_Out_Parameter);
10691 else
10692 Set_Ekind (Formal_Id, E_Out_Parameter);
10693 Set_Never_Set_In_Source (Formal_Id, True);
10694 Set_Is_True_Constant (Formal_Id, False);
10695 Set_Current_Value (Formal_Id, Empty);
10696 end if;
10698 else
10699 Set_Ekind (Formal_Id, E_In_Parameter);
10700 end if;
10702 -- Set Is_Known_Non_Null for access parameters since the language
10703 -- guarantees that access parameters are always non-null. We also set
10704 -- Can_Never_Be_Null, since there is no way to change the value.
10706 if Nkind (Parameter_Type (Spec)) = N_Access_Definition then
10708 -- Ada 2005 (AI-231): In Ada 95, access parameters are always non-
10709 -- null; In Ada 2005, only if then null_exclusion is explicit.
10711 if Ada_Version < Ada_2005
10712 or else Can_Never_Be_Null (Etype (Formal_Id))
10713 then
10714 Set_Is_Known_Non_Null (Formal_Id);
10715 Set_Can_Never_Be_Null (Formal_Id);
10716 end if;
10718 -- Ada 2005 (AI-231): Null-exclusion access subtype
10720 elsif Is_Access_Type (Etype (Formal_Id))
10721 and then Can_Never_Be_Null (Etype (Formal_Id))
10722 then
10723 Set_Is_Known_Non_Null (Formal_Id);
10725 -- We can also set Can_Never_Be_Null (thus preventing some junk
10726 -- access checks) for the case of an IN parameter, which cannot
10727 -- be changed, or for an IN OUT parameter, which can be changed but
10728 -- not to a null value. But for an OUT parameter, the initial value
10729 -- passed in can be null, so we can't set this flag in that case.
10731 if Ekind (Formal_Id) /= E_Out_Parameter then
10732 Set_Can_Never_Be_Null (Formal_Id);
10733 end if;
10734 end if;
10736 Set_Mechanism (Formal_Id, Default_Mechanism);
10737 Set_Formal_Validity (Formal_Id);
10738 end Set_Formal_Mode;
10740 -------------------------
10741 -- Set_Formal_Validity --
10742 -------------------------
10744 procedure Set_Formal_Validity (Formal_Id : Entity_Id) is
10745 begin
10746 -- If no validity checking, then we cannot assume anything about the
10747 -- validity of parameters, since we do not know there is any checking
10748 -- of the validity on the call side.
10750 if not Validity_Checks_On then
10751 return;
10753 -- If validity checking for parameters is enabled, this means we are
10754 -- not supposed to make any assumptions about argument values.
10756 elsif Validity_Check_Parameters then
10757 return;
10759 -- If we are checking in parameters, we will assume that the caller is
10760 -- also checking parameters, so we can assume the parameter is valid.
10762 elsif Ekind (Formal_Id) = E_In_Parameter
10763 and then Validity_Check_In_Params
10764 then
10765 Set_Is_Known_Valid (Formal_Id, True);
10767 -- Similar treatment for IN OUT parameters
10769 elsif Ekind (Formal_Id) = E_In_Out_Parameter
10770 and then Validity_Check_In_Out_Params
10771 then
10772 Set_Is_Known_Valid (Formal_Id, True);
10773 end if;
10774 end Set_Formal_Validity;
10776 ------------------------
10777 -- Subtype_Conformant --
10778 ------------------------
10780 function Subtype_Conformant
10781 (New_Id : Entity_Id;
10782 Old_Id : Entity_Id;
10783 Skip_Controlling_Formals : Boolean := False) return Boolean
10785 Result : Boolean;
10786 begin
10787 Check_Conformance (New_Id, Old_Id, Subtype_Conformant, False, Result,
10788 Skip_Controlling_Formals => Skip_Controlling_Formals);
10789 return Result;
10790 end Subtype_Conformant;
10792 ---------------------
10793 -- Type_Conformant --
10794 ---------------------
10796 function Type_Conformant
10797 (New_Id : Entity_Id;
10798 Old_Id : Entity_Id;
10799 Skip_Controlling_Formals : Boolean := False) return Boolean
10801 Result : Boolean;
10802 begin
10803 May_Hide_Profile := False;
10804 Check_Conformance
10805 (New_Id, Old_Id, Type_Conformant, False, Result,
10806 Skip_Controlling_Formals => Skip_Controlling_Formals);
10807 return Result;
10808 end Type_Conformant;
10810 -------------------------------
10811 -- Valid_Operator_Definition --
10812 -------------------------------
10814 procedure Valid_Operator_Definition (Designator : Entity_Id) is
10815 N : Integer := 0;
10816 F : Entity_Id;
10817 Id : constant Name_Id := Chars (Designator);
10818 N_OK : Boolean;
10820 begin
10821 F := First_Formal (Designator);
10822 while Present (F) loop
10823 N := N + 1;
10825 if Present (Default_Value (F)) then
10826 Error_Msg_N
10827 ("default values not allowed for operator parameters",
10828 Parent (F));
10830 -- For function instantiations that are operators, we must check
10831 -- separately that the corresponding generic only has in-parameters.
10832 -- For subprogram declarations this is done in Set_Formal_Mode. Such
10833 -- an error could not arise in earlier versions of the language.
10835 elsif Ekind (F) /= E_In_Parameter then
10836 Error_Msg_N ("operators can only have IN parameters", F);
10837 end if;
10839 Next_Formal (F);
10840 end loop;
10842 -- Verify that user-defined operators have proper number of arguments
10843 -- First case of operators which can only be unary
10845 if Nam_In (Id, Name_Op_Not, Name_Op_Abs) then
10846 N_OK := (N = 1);
10848 -- Case of operators which can be unary or binary
10850 elsif Nam_In (Id, Name_Op_Add, Name_Op_Subtract) then
10851 N_OK := (N in 1 .. 2);
10853 -- All other operators can only be binary
10855 else
10856 N_OK := (N = 2);
10857 end if;
10859 if not N_OK then
10860 Error_Msg_N
10861 ("incorrect number of arguments for operator", Designator);
10862 end if;
10864 if Id = Name_Op_Ne
10865 and then Base_Type (Etype (Designator)) = Standard_Boolean
10866 and then not Is_Intrinsic_Subprogram (Designator)
10867 then
10868 Error_Msg_N
10869 ("explicit definition of inequality not allowed", Designator);
10870 end if;
10871 end Valid_Operator_Definition;
10873 end Sem_Ch6;