* config/rs6000/rs6000.md: Document why a pattern is not
[official-gcc.git] / gcc / ada / exp_ch6.adb
blob1bfb5c1c86d929c4fe9bec691b33356e4e228b50
1 ------------------------------------------------------------------------------
2 -- --
3 -- GNAT COMPILER COMPONENTS --
4 -- --
5 -- E X P _ C H 6 --
6 -- --
7 -- B o d y --
8 -- --
9 -- Copyright (C) 1992-2004, Free Software Foundation, Inc. --
10 -- --
11 -- GNAT is free software; you can redistribute it and/or modify it under --
12 -- terms of the GNU General Public License as published by the Free Soft- --
13 -- ware Foundation; either version 2, or (at your option) any later ver- --
14 -- sion. GNAT is distributed in the hope that it will be useful, but WITH- --
15 -- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY --
16 -- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License --
17 -- for more details. You should have received a copy of the GNU General --
18 -- Public License distributed with GNAT; see file COPYING. If not, write --
19 -- to the Free Software Foundation, 59 Temple Place - Suite 330, Boston, --
20 -- MA 02111-1307, USA. --
21 -- --
22 -- GNAT was originally developed by the GNAT team at New York University. --
23 -- Extensive contributions were provided by Ada Core Technologies Inc. --
24 -- --
25 ------------------------------------------------------------------------------
27 with Atree; use Atree;
28 with Checks; use Checks;
29 with Debug; use Debug;
30 with Einfo; use Einfo;
31 with Errout; use Errout;
32 with Elists; use Elists;
33 with Exp_Ch2; use Exp_Ch2;
34 with Exp_Ch3; use Exp_Ch3;
35 with Exp_Ch7; use Exp_Ch7;
36 with Exp_Ch9; use Exp_Ch9;
37 with Exp_Ch11; use Exp_Ch11;
38 with Exp_Dbug; use Exp_Dbug;
39 with Exp_Disp; use Exp_Disp;
40 with Exp_Dist; use Exp_Dist;
41 with Exp_Intr; use Exp_Intr;
42 with Exp_Pakd; use Exp_Pakd;
43 with Exp_Tss; use Exp_Tss;
44 with Exp_Util; use Exp_Util;
45 with Fname; use Fname;
46 with Freeze; use Freeze;
47 with Hostparm; use Hostparm;
48 with Inline; use Inline;
49 with Lib; use Lib;
50 with Nlists; use Nlists;
51 with Nmake; use Nmake;
52 with Opt; use Opt;
53 with Restrict; use Restrict;
54 with Rident; use Rident;
55 with Rtsfind; use Rtsfind;
56 with Sem; use Sem;
57 with Sem_Ch6; use Sem_Ch6;
58 with Sem_Ch8; use Sem_Ch8;
59 with Sem_Ch12; use Sem_Ch12;
60 with Sem_Ch13; use Sem_Ch13;
61 with Sem_Disp; use Sem_Disp;
62 with Sem_Dist; use Sem_Dist;
63 with Sem_Res; use Sem_Res;
64 with Sem_Util; use Sem_Util;
65 with Sinfo; use Sinfo;
66 with Snames; use Snames;
67 with Stand; use Stand;
68 with Tbuild; use Tbuild;
69 with Ttypes; use Ttypes;
70 with Uintp; use Uintp;
71 with Validsw; use Validsw;
73 package body Exp_Ch6 is
75 -----------------------
76 -- Local Subprograms --
77 -----------------------
79 procedure Check_Overriding_Operation (Subp : Entity_Id);
80 -- Subp is a dispatching operation. Check whether it may override an
81 -- inherited private operation, in which case its DT entry is that of
82 -- the hidden operation, not the one it may have received earlier.
83 -- This must be done before emitting the code to set the corresponding
84 -- DT to the address of the subprogram. The actual placement of Subp in
85 -- the proper place in the list of primitive operations is done in
86 -- Declare_Inherited_Private_Subprograms, which also has to deal with
87 -- implicit operations. This duplication is unavoidable for now???
89 procedure Detect_Infinite_Recursion (N : Node_Id; Spec : Entity_Id);
90 -- This procedure is called only if the subprogram body N, whose spec
91 -- has the given entity Spec, contains a parameterless recursive call.
92 -- It attempts to generate runtime code to detect if this a case of
93 -- infinite recursion.
95 -- The body is scanned to determine dependencies. If the only external
96 -- dependencies are on a small set of scalar variables, then the values
97 -- of these variables are captured on entry to the subprogram, and if
98 -- the values are not changed for the call, we know immediately that
99 -- we have an infinite recursion.
101 procedure Expand_Actuals (N : Node_Id; Subp : Entity_Id);
102 -- For each actual of an in-out parameter which is a numeric conversion
103 -- of the form T(A), where A denotes a variable, we insert the declaration:
105 -- Temp : T := T (A);
107 -- prior to the call. Then we replace the actual with a reference to Temp,
108 -- and append the assignment:
110 -- A := TypeA (Temp);
112 -- after the call. Here TypeA is the actual type of variable A.
113 -- For out parameters, the initial declaration has no expression.
114 -- If A is not an entity name, we generate instead:
116 -- Var : TypeA renames A;
117 -- Temp : T := Var; -- omitting expression for out parameter.
118 -- ...
119 -- Var := TypeA (Temp);
121 -- For other in-out parameters, we emit the required constraint checks
122 -- before and/or after the call.
124 -- For all parameter modes, actuals that denote components and slices
125 -- of packed arrays are expanded into suitable temporaries.
127 procedure Expand_Inlined_Call
128 (N : Node_Id;
129 Subp : Entity_Id;
130 Orig_Subp : Entity_Id);
131 -- If called subprogram can be inlined by the front-end, retrieve the
132 -- analyzed body, replace formals with actuals and expand call in place.
133 -- Generate thunks for actuals that are expressions, and insert the
134 -- corresponding constant declarations before the call. If the original
135 -- call is to a derived operation, the return type is the one of the
136 -- derived operation, but the body is that of the original, so return
137 -- expressions in the body must be converted to the desired type (which
138 -- is simply not noted in the tree without inline expansion).
140 function Expand_Protected_Object_Reference
141 (N : Node_Id;
142 Scop : Entity_Id)
143 return Node_Id;
145 procedure Expand_Protected_Subprogram_Call
146 (N : Node_Id;
147 Subp : Entity_Id;
148 Scop : Entity_Id);
149 -- A call to a protected subprogram within the protected object may appear
150 -- as a regular call. The list of actuals must be expanded to contain a
151 -- reference to the object itself, and the call becomes a call to the
152 -- corresponding protected subprogram.
154 --------------------------------
155 -- Check_Overriding_Operation --
156 --------------------------------
158 procedure Check_Overriding_Operation (Subp : Entity_Id) is
159 Typ : constant Entity_Id := Find_Dispatching_Type (Subp);
160 Op_List : constant Elist_Id := Primitive_Operations (Typ);
161 Op_Elmt : Elmt_Id;
162 Prim_Op : Entity_Id;
163 Par_Op : Entity_Id;
165 begin
166 if Is_Derived_Type (Typ)
167 and then not Is_Private_Type (Typ)
168 and then In_Open_Scopes (Scope (Etype (Typ)))
169 and then Typ = Base_Type (Typ)
170 then
171 -- Subp overrides an inherited private operation if there is
172 -- an inherited operation with a different name than Subp (see
173 -- Derive_Subprogram) whose Alias is a hidden subprogram with
174 -- the same name as Subp.
176 Op_Elmt := First_Elmt (Op_List);
177 while Present (Op_Elmt) loop
178 Prim_Op := Node (Op_Elmt);
179 Par_Op := Alias (Prim_Op);
181 if Present (Par_Op)
182 and then not Comes_From_Source (Prim_Op)
183 and then Chars (Prim_Op) /= Chars (Par_Op)
184 and then Chars (Par_Op) = Chars (Subp)
185 and then Is_Hidden (Par_Op)
186 and then Type_Conformant (Prim_Op, Subp)
187 then
188 Set_DT_Position (Subp, DT_Position (Prim_Op));
189 end if;
191 Next_Elmt (Op_Elmt);
192 end loop;
193 end if;
194 end Check_Overriding_Operation;
196 -------------------------------
197 -- Detect_Infinite_Recursion --
198 -------------------------------
200 procedure Detect_Infinite_Recursion (N : Node_Id; Spec : Entity_Id) is
201 Loc : constant Source_Ptr := Sloc (N);
203 Var_List : constant Elist_Id := New_Elmt_List;
204 -- List of globals referenced by body of procedure
206 Call_List : constant Elist_Id := New_Elmt_List;
207 -- List of recursive calls in body of procedure
209 Shad_List : constant Elist_Id := New_Elmt_List;
210 -- List of entity id's for entities created to capture the
211 -- value of referenced globals on entry to the procedure.
213 Scop : constant Uint := Scope_Depth (Spec);
214 -- This is used to record the scope depth of the current
215 -- procedure, so that we can identify global references.
217 Max_Vars : constant := 4;
218 -- Do not test more than four global variables
220 Count_Vars : Natural := 0;
221 -- Count variables found so far
223 Var : Entity_Id;
224 Elm : Elmt_Id;
225 Ent : Entity_Id;
226 Call : Elmt_Id;
227 Decl : Node_Id;
228 Test : Node_Id;
229 Elm1 : Elmt_Id;
230 Elm2 : Elmt_Id;
231 Last : Node_Id;
233 function Process (Nod : Node_Id) return Traverse_Result;
234 -- Function to traverse the subprogram body (using Traverse_Func)
236 -------------
237 -- Process --
238 -------------
240 function Process (Nod : Node_Id) return Traverse_Result is
241 begin
242 -- Procedure call
244 if Nkind (Nod) = N_Procedure_Call_Statement then
246 -- Case of one of the detected recursive calls
248 if Is_Entity_Name (Name (Nod))
249 and then Has_Recursive_Call (Entity (Name (Nod)))
250 and then Entity (Name (Nod)) = Spec
251 then
252 Append_Elmt (Nod, Call_List);
253 return Skip;
255 -- Any other procedure call may have side effects
257 else
258 return Abandon;
259 end if;
261 -- A call to a pure function can always be ignored
263 elsif Nkind (Nod) = N_Function_Call
264 and then Is_Entity_Name (Name (Nod))
265 and then Is_Pure (Entity (Name (Nod)))
266 then
267 return Skip;
269 -- Case of an identifier reference
271 elsif Nkind (Nod) = N_Identifier then
272 Ent := Entity (Nod);
274 -- If no entity, then ignore the reference
276 -- Not clear why this can happen. To investigate, remove this
277 -- test and look at the crash that occurs here in 3401-004 ???
279 if No (Ent) then
280 return Skip;
282 -- Ignore entities with no Scope, again not clear how this
283 -- can happen, to investigate, look at 4108-008 ???
285 elsif No (Scope (Ent)) then
286 return Skip;
288 -- Ignore the reference if not to a more global object
290 elsif Scope_Depth (Scope (Ent)) >= Scop then
291 return Skip;
293 -- References to types, exceptions and constants are always OK
295 elsif Is_Type (Ent)
296 or else Ekind (Ent) = E_Exception
297 or else Ekind (Ent) = E_Constant
298 then
299 return Skip;
301 -- If other than a non-volatile scalar variable, we have some
302 -- kind of global reference (e.g. to a function) that we cannot
303 -- deal with so we forget the attempt.
305 elsif Ekind (Ent) /= E_Variable
306 or else not Is_Scalar_Type (Etype (Ent))
307 or else Treat_As_Volatile (Ent)
308 then
309 return Abandon;
311 -- Otherwise we have a reference to a global scalar
313 else
314 -- Loop through global entities already detected
316 Elm := First_Elmt (Var_List);
317 loop
318 -- If not detected before, record this new global reference
320 if No (Elm) then
321 Count_Vars := Count_Vars + 1;
323 if Count_Vars <= Max_Vars then
324 Append_Elmt (Entity (Nod), Var_List);
325 else
326 return Abandon;
327 end if;
329 exit;
331 -- If recorded before, ignore
333 elsif Node (Elm) = Entity (Nod) then
334 return Skip;
336 -- Otherwise keep looking
338 else
339 Next_Elmt (Elm);
340 end if;
341 end loop;
343 return Skip;
344 end if;
346 -- For all other node kinds, recursively visit syntactic children
348 else
349 return OK;
350 end if;
351 end Process;
353 function Traverse_Body is new Traverse_Func;
355 -- Start of processing for Detect_Infinite_Recursion
357 begin
358 -- Do not attempt detection in No_Implicit_Conditional mode,
359 -- since we won't be able to generate the code to handle the
360 -- recursion in any case.
362 if Restriction_Active (No_Implicit_Conditionals) then
363 return;
364 end if;
366 -- Otherwise do traversal and quit if we get abandon signal
368 if Traverse_Body (N) = Abandon then
369 return;
371 -- We must have a call, since Has_Recursive_Call was set. If not
372 -- just ignore (this is only an error check, so if we have a funny
373 -- situation, due to bugs or errors, we do not want to bomb!)
375 elsif Is_Empty_Elmt_List (Call_List) then
376 return;
377 end if;
379 -- Here is the case where we detect recursion at compile time
381 -- Push our current scope for analyzing the declarations and
382 -- code that we will insert for the checking.
384 New_Scope (Spec);
386 -- This loop builds temporary variables for each of the
387 -- referenced globals, so that at the end of the loop the
388 -- list Shad_List contains these temporaries in one-to-one
389 -- correspondence with the elements in Var_List.
391 Last := Empty;
392 Elm := First_Elmt (Var_List);
393 while Present (Elm) loop
394 Var := Node (Elm);
395 Ent :=
396 Make_Defining_Identifier (Loc,
397 Chars => New_Internal_Name ('S'));
398 Append_Elmt (Ent, Shad_List);
400 -- Insert a declaration for this temporary at the start of
401 -- the declarations for the procedure. The temporaries are
402 -- declared as constant objects initialized to the current
403 -- values of the corresponding temporaries.
405 Decl :=
406 Make_Object_Declaration (Loc,
407 Defining_Identifier => Ent,
408 Object_Definition => New_Occurrence_Of (Etype (Var), Loc),
409 Constant_Present => True,
410 Expression => New_Occurrence_Of (Var, Loc));
412 if No (Last) then
413 Prepend (Decl, Declarations (N));
414 else
415 Insert_After (Last, Decl);
416 end if;
418 Last := Decl;
419 Analyze (Decl);
420 Next_Elmt (Elm);
421 end loop;
423 -- Loop through calls
425 Call := First_Elmt (Call_List);
426 while Present (Call) loop
428 -- Build a predicate expression of the form
430 -- True
431 -- and then global1 = temp1
432 -- and then global2 = temp2
433 -- ...
435 -- This predicate determines if any of the global values
436 -- referenced by the procedure have changed since the
437 -- current call, if not an infinite recursion is assured.
439 Test := New_Occurrence_Of (Standard_True, Loc);
441 Elm1 := First_Elmt (Var_List);
442 Elm2 := First_Elmt (Shad_List);
443 while Present (Elm1) loop
444 Test :=
445 Make_And_Then (Loc,
446 Left_Opnd => Test,
447 Right_Opnd =>
448 Make_Op_Eq (Loc,
449 Left_Opnd => New_Occurrence_Of (Node (Elm1), Loc),
450 Right_Opnd => New_Occurrence_Of (Node (Elm2), Loc)));
452 Next_Elmt (Elm1);
453 Next_Elmt (Elm2);
454 end loop;
456 -- Now we replace the call with the sequence
458 -- if no-changes (see above) then
459 -- raise Storage_Error;
460 -- else
461 -- original-call
462 -- end if;
464 Rewrite (Node (Call),
465 Make_If_Statement (Loc,
466 Condition => Test,
467 Then_Statements => New_List (
468 Make_Raise_Storage_Error (Loc,
469 Reason => SE_Infinite_Recursion)),
471 Else_Statements => New_List (
472 Relocate_Node (Node (Call)))));
474 Analyze (Node (Call));
476 Next_Elmt (Call);
477 end loop;
479 -- Remove temporary scope stack entry used for analysis
481 Pop_Scope;
482 end Detect_Infinite_Recursion;
484 --------------------
485 -- Expand_Actuals --
486 --------------------
488 procedure Expand_Actuals (N : Node_Id; Subp : Entity_Id) is
489 Loc : constant Source_Ptr := Sloc (N);
490 Actual : Node_Id;
491 Formal : Entity_Id;
492 N_Node : Node_Id;
493 Post_Call : List_Id;
494 E_Formal : Entity_Id;
496 procedure Add_Call_By_Copy_Code;
497 -- For cases where the parameter must be passed by copy, this routine
498 -- generates a temporary variable into which the actual is copied and
499 -- then passes this as the parameter. For an OUT or IN OUT parameter,
500 -- an assignment is also generated to copy the result back. The call
501 -- also takes care of any constraint checks required for the type
502 -- conversion case (on both the way in and the way out).
504 procedure Add_Packed_Call_By_Copy_Code;
505 -- This is used when the actual involves a reference to an element
506 -- of a packed array, where we can appropriately use a simpler
507 -- approach than the full call by copy code. We just copy the value
508 -- in and out of an appropriate temporary.
510 procedure Check_Fortran_Logical;
511 -- A value of type Logical that is passed through a formal parameter
512 -- must be normalized because .TRUE. usually does not have the same
513 -- representation as True. We assume that .FALSE. = False = 0.
514 -- What about functions that return a logical type ???
516 function Make_Var (Actual : Node_Id) return Entity_Id;
517 -- Returns an entity that refers to the given actual parameter,
518 -- Actual (not including any type conversion). If Actual is an
519 -- entity name, then this entity is returned unchanged, otherwise
520 -- a renaming is created to provide an entity for the actual.
522 procedure Reset_Packed_Prefix;
523 -- The expansion of a packed array component reference is delayed in
524 -- the context of a call. Now we need to complete the expansion, so we
525 -- unmark the analyzed bits in all prefixes.
527 ---------------------------
528 -- Add_Call_By_Copy_Code --
529 ---------------------------
531 procedure Add_Call_By_Copy_Code is
532 Expr : Node_Id;
533 Init : Node_Id;
534 Temp : Entity_Id;
535 Var : Entity_Id;
536 V_Typ : Entity_Id;
537 Crep : Boolean;
539 begin
540 Temp := Make_Defining_Identifier (Loc, New_Internal_Name ('T'));
542 if Nkind (Actual) = N_Type_Conversion then
543 V_Typ := Etype (Expression (Actual));
545 -- If the formal is an (in-)out parameter, capture the name
546 -- of the variable in order to build the post-call assignment.
548 Var := Make_Var (Expression (Actual));
550 Crep := not Same_Representation
551 (Etype (Formal), Etype (Expression (Actual)));
553 else
554 V_Typ := Etype (Actual);
555 Var := Make_Var (Actual);
556 Crep := False;
557 end if;
559 -- Setup initialization for case of in out parameter, or an out
560 -- parameter where the formal is an unconstrained array (in the
561 -- latter case, we have to pass in an object with bounds).
563 if Ekind (Formal) = E_In_Out_Parameter
564 or else (Is_Array_Type (Etype (Formal))
565 and then
566 not Is_Constrained (Etype (Formal)))
567 then
568 if Nkind (Actual) = N_Type_Conversion then
569 if Conversion_OK (Actual) then
570 Init := OK_Convert_To
571 (Etype (Formal), New_Occurrence_Of (Var, Loc));
572 else
573 Init := Convert_To
574 (Etype (Formal), New_Occurrence_Of (Var, Loc));
575 end if;
576 else
577 Init := New_Occurrence_Of (Var, Loc);
578 end if;
580 -- An initialization is created for packed conversions as
581 -- actuals for out parameters to enable Make_Object_Declaration
582 -- to determine the proper subtype for N_Node. Note that this
583 -- is wasteful because the extra copying on the call side is
584 -- not required for such out parameters. ???
586 elsif Ekind (Formal) = E_Out_Parameter
587 and then Nkind (Actual) = N_Type_Conversion
588 and then (Is_Bit_Packed_Array (Etype (Formal))
589 or else
590 Is_Bit_Packed_Array (Etype (Expression (Actual))))
591 then
592 if Conversion_OK (Actual) then
593 Init :=
594 OK_Convert_To (Etype (Formal), New_Occurrence_Of (Var, Loc));
595 else
596 Init :=
597 Convert_To (Etype (Formal), New_Occurrence_Of (Var, Loc));
598 end if;
600 elsif Ekind (Formal) = E_In_Parameter then
601 Init := New_Occurrence_Of (Var, Loc);
603 else
604 Init := Empty;
605 end if;
607 N_Node :=
608 Make_Object_Declaration (Loc,
609 Defining_Identifier => Temp,
610 Object_Definition =>
611 New_Occurrence_Of (Etype (Formal), Loc),
612 Expression => Init);
613 Set_Assignment_OK (N_Node);
614 Insert_Action (N, N_Node);
616 -- Now, normally the deal here is that we use the defining
617 -- identifier created by that object declaration. There is
618 -- one exception to this. In the change of representation case
619 -- the above declaration will end up looking like:
621 -- temp : type := identifier;
623 -- And in this case we might as well use the identifier directly
624 -- and eliminate the temporary. Note that the analysis of the
625 -- declaration was not a waste of time in that case, since it is
626 -- what generated the necessary change of representation code. If
627 -- the change of representation introduced additional code, as in
628 -- a fixed-integer conversion, the expression is not an identifier
629 -- and must be kept.
631 if Crep
632 and then Present (Expression (N_Node))
633 and then Is_Entity_Name (Expression (N_Node))
634 then
635 Temp := Entity (Expression (N_Node));
636 Rewrite (N_Node, Make_Null_Statement (Loc));
637 end if;
639 -- For IN parameter, all we do is to replace the actual
641 if Ekind (Formal) = E_In_Parameter then
642 Rewrite (Actual, New_Reference_To (Temp, Loc));
643 Analyze (Actual);
645 -- Processing for OUT or IN OUT parameter
647 else
648 -- If type conversion, use reverse conversion on exit
650 if Nkind (Actual) = N_Type_Conversion then
651 if Conversion_OK (Actual) then
652 Expr := OK_Convert_To (V_Typ, New_Occurrence_Of (Temp, Loc));
653 else
654 Expr := Convert_To (V_Typ, New_Occurrence_Of (Temp, Loc));
655 end if;
656 else
657 Expr := New_Occurrence_Of (Temp, Loc);
658 end if;
660 Rewrite (Actual, New_Reference_To (Temp, Loc));
661 Analyze (Actual);
663 Append_To (Post_Call,
664 Make_Assignment_Statement (Loc,
665 Name => New_Occurrence_Of (Var, Loc),
666 Expression => Expr));
668 Set_Assignment_OK (Name (Last (Post_Call)));
669 end if;
670 end Add_Call_By_Copy_Code;
672 ----------------------------------
673 -- Add_Packed_Call_By_Copy_Code --
674 ----------------------------------
676 procedure Add_Packed_Call_By_Copy_Code is
677 Temp : Entity_Id;
678 Incod : Node_Id;
679 Outcod : Node_Id;
680 Lhs : Node_Id;
681 Rhs : Node_Id;
683 begin
684 Reset_Packed_Prefix;
686 -- Prepare to generate code
688 Temp := Make_Defining_Identifier (Loc, New_Internal_Name ('T'));
689 Incod := Relocate_Node (Actual);
690 Outcod := New_Copy_Tree (Incod);
692 -- Generate declaration of temporary variable, initializing it
693 -- with the input parameter unless we have an OUT variable.
695 if Ekind (Formal) = E_Out_Parameter then
696 Incod := Empty;
697 end if;
699 Insert_Action (N,
700 Make_Object_Declaration (Loc,
701 Defining_Identifier => Temp,
702 Object_Definition =>
703 New_Occurrence_Of (Etype (Formal), Loc),
704 Expression => Incod));
706 -- The actual is simply a reference to the temporary
708 Rewrite (Actual, New_Occurrence_Of (Temp, Loc));
710 -- Generate copy out if OUT or IN OUT parameter
712 if Ekind (Formal) /= E_In_Parameter then
713 Lhs := Outcod;
714 Rhs := New_Occurrence_Of (Temp, Loc);
716 -- Deal with conversion
718 if Nkind (Lhs) = N_Type_Conversion then
719 Lhs := Expression (Lhs);
720 Rhs := Convert_To (Etype (Actual), Rhs);
721 end if;
723 Append_To (Post_Call,
724 Make_Assignment_Statement (Loc,
725 Name => Lhs,
726 Expression => Rhs));
727 end if;
728 end Add_Packed_Call_By_Copy_Code;
730 ---------------------------
731 -- Check_Fortran_Logical --
732 ---------------------------
734 procedure Check_Fortran_Logical is
735 Logical : constant Entity_Id := Etype (Formal);
736 Var : Entity_Id;
738 -- Note: this is very incomplete, e.g. it does not handle arrays
739 -- of logical values. This is really not the right approach at all???)
741 begin
742 if Convention (Subp) = Convention_Fortran
743 and then Root_Type (Etype (Formal)) = Standard_Boolean
744 and then Ekind (Formal) /= E_In_Parameter
745 then
746 Var := Make_Var (Actual);
747 Append_To (Post_Call,
748 Make_Assignment_Statement (Loc,
749 Name => New_Occurrence_Of (Var, Loc),
750 Expression =>
751 Unchecked_Convert_To (
752 Logical,
753 Make_Op_Ne (Loc,
754 Left_Opnd => New_Occurrence_Of (Var, Loc),
755 Right_Opnd =>
756 Unchecked_Convert_To (
757 Logical,
758 New_Occurrence_Of (Standard_False, Loc))))));
759 end if;
760 end Check_Fortran_Logical;
762 --------------
763 -- Make_Var --
764 --------------
766 function Make_Var (Actual : Node_Id) return Entity_Id is
767 Var : Entity_Id;
769 begin
770 if Is_Entity_Name (Actual) then
771 return Entity (Actual);
773 else
774 Var := Make_Defining_Identifier (Loc, New_Internal_Name ('T'));
776 N_Node :=
777 Make_Object_Renaming_Declaration (Loc,
778 Defining_Identifier => Var,
779 Subtype_Mark =>
780 New_Occurrence_Of (Etype (Actual), Loc),
781 Name => Relocate_Node (Actual));
783 Insert_Action (N, N_Node);
784 return Var;
785 end if;
786 end Make_Var;
788 -------------------------
789 -- Reset_Packed_Prefix --
790 -------------------------
792 procedure Reset_Packed_Prefix is
793 Pfx : Node_Id := Actual;
795 begin
796 loop
797 Set_Analyzed (Pfx, False);
798 exit when Nkind (Pfx) /= N_Selected_Component
799 and then Nkind (Pfx) /= N_Indexed_Component;
800 Pfx := Prefix (Pfx);
801 end loop;
802 end Reset_Packed_Prefix;
804 -- Start of processing for Expand_Actuals
806 begin
807 Formal := First_Formal (Subp);
808 Actual := First_Actual (N);
810 Post_Call := New_List;
812 while Present (Formal) loop
813 E_Formal := Etype (Formal);
815 if Is_Scalar_Type (E_Formal)
816 or else Nkind (Actual) = N_Slice
817 then
818 Check_Fortran_Logical;
820 -- RM 6.4.1 (11)
822 elsif Ekind (Formal) /= E_Out_Parameter then
824 -- The unusual case of the current instance of a protected type
825 -- requires special handling. This can only occur in the context
826 -- of a call within the body of a protected operation.
828 if Is_Entity_Name (Actual)
829 and then Ekind (Entity (Actual)) = E_Protected_Type
830 and then In_Open_Scopes (Entity (Actual))
831 then
832 if Scope (Subp) /= Entity (Actual) then
833 Error_Msg_N ("operation outside protected type may not "
834 & "call back its protected operations?", Actual);
835 end if;
837 Rewrite (Actual,
838 Expand_Protected_Object_Reference (N, Entity (Actual)));
839 end if;
841 Apply_Constraint_Check (Actual, E_Formal);
843 -- Out parameter case. No constraint checks on access type
844 -- RM 6.4.1 (13)
846 elsif Is_Access_Type (E_Formal) then
847 null;
849 -- RM 6.4.1 (14)
851 elsif Has_Discriminants (Base_Type (E_Formal))
852 or else Has_Non_Null_Base_Init_Proc (E_Formal)
853 then
854 Apply_Constraint_Check (Actual, E_Formal);
856 -- RM 6.4.1 (15)
858 else
859 Apply_Constraint_Check (Actual, Base_Type (E_Formal));
860 end if;
862 -- Processing for IN-OUT and OUT parameters
864 if Ekind (Formal) /= E_In_Parameter then
866 -- For type conversions of arrays, apply length/range checks
868 if Is_Array_Type (E_Formal)
869 and then Nkind (Actual) = N_Type_Conversion
870 then
871 if Is_Constrained (E_Formal) then
872 Apply_Length_Check (Expression (Actual), E_Formal);
873 else
874 Apply_Range_Check (Expression (Actual), E_Formal);
875 end if;
876 end if;
878 -- If argument is a type conversion for a type that is passed
879 -- by copy, then we must pass the parameter by copy.
881 if Nkind (Actual) = N_Type_Conversion
882 and then
883 (Is_Numeric_Type (E_Formal)
884 or else Is_Access_Type (E_Formal)
885 or else Is_Enumeration_Type (E_Formal)
886 or else Is_Bit_Packed_Array (Etype (Formal))
887 or else Is_Bit_Packed_Array (Etype (Expression (Actual)))
889 -- Also pass by copy if change of representation
891 or else not Same_Representation
892 (Etype (Formal),
893 Etype (Expression (Actual))))
894 then
895 Add_Call_By_Copy_Code;
897 -- References to components of bit packed arrays are expanded
898 -- at this point, rather than at the point of analysis of the
899 -- actuals, to handle the expansion of the assignment to
900 -- [in] out parameters.
902 elsif Is_Ref_To_Bit_Packed_Array (Actual) then
903 Add_Packed_Call_By_Copy_Code;
905 -- References to slices of bit packed arrays are expanded
907 elsif Is_Ref_To_Bit_Packed_Slice (Actual) then
908 Add_Call_By_Copy_Code;
910 -- References to possibly unaligned slices of arrays are expanded
912 elsif Is_Possibly_Unaligned_Slice (Actual) then
913 Add_Call_By_Copy_Code;
915 -- Deal with access types where the actual subtpe and the
916 -- formal subtype are not the same, requiring a check.
918 -- It is necessary to exclude tagged types because of "downward
919 -- conversion" errors and a strange assertion error in namet
920 -- from gnatf in bug 1215-001 ???
922 elsif Is_Access_Type (E_Formal)
923 and then not Same_Type (E_Formal, Etype (Actual))
924 and then not Is_Tagged_Type (Designated_Type (E_Formal))
925 then
926 Add_Call_By_Copy_Code;
928 elsif Is_Entity_Name (Actual)
929 and then Treat_As_Volatile (Entity (Actual))
930 and then not Is_Scalar_Type (Etype (Entity (Actual)))
931 and then not Treat_As_Volatile (E_Formal)
932 then
933 Add_Call_By_Copy_Code;
935 elsif Nkind (Actual) = N_Indexed_Component
936 and then Is_Entity_Name (Prefix (Actual))
937 and then Has_Volatile_Components (Entity (Prefix (Actual)))
938 then
939 Add_Call_By_Copy_Code;
940 end if;
942 -- Processing for IN parameters
944 else
945 -- For IN parameters is in the packed array case, we expand an
946 -- indexed component (the circuit in Exp_Ch4 deliberately left
947 -- indexed components appearing as actuals untouched, so that
948 -- the special processing above for the OUT and IN OUT cases
949 -- could be performed. We could make the test in Exp_Ch4 more
950 -- complex and have it detect the parameter mode, but it is
951 -- easier simply to handle all cases here.
953 if Nkind (Actual) = N_Indexed_Component
954 and then Is_Packed (Etype (Prefix (Actual)))
955 then
956 Reset_Packed_Prefix;
957 Expand_Packed_Element_Reference (Actual);
959 -- If we have a reference to a bit packed array, we copy it,
960 -- since the actual must be byte aligned.
962 -- Is this really necessary in all cases???
964 elsif Is_Ref_To_Bit_Packed_Array (Actual) then
965 Add_Packed_Call_By_Copy_Code;
967 -- Similarly, we have to expand slices of packed arrays here
968 -- because the result must be byte aligned.
970 elsif Is_Ref_To_Bit_Packed_Slice (Actual) then
971 Add_Call_By_Copy_Code;
973 -- Only processing remaining is to pass by copy if this is a
974 -- reference to a possibly unaligned slice, since the caller
975 -- expects an appropriately aligned argument.
977 elsif Is_Possibly_Unaligned_Slice (Actual) then
978 Add_Call_By_Copy_Code;
979 end if;
980 end if;
982 Next_Formal (Formal);
983 Next_Actual (Actual);
984 end loop;
986 -- Find right place to put post call stuff if it is present
988 if not Is_Empty_List (Post_Call) then
990 -- If call is not a list member, it must be the triggering
991 -- statement of a triggering alternative or an entry call
992 -- alternative, and we can add the post call stuff to the
993 -- corresponding statement list.
995 if not Is_List_Member (N) then
996 declare
997 P : constant Node_Id := Parent (N);
999 begin
1000 pragma Assert (Nkind (P) = N_Triggering_Alternative
1001 or else Nkind (P) = N_Entry_Call_Alternative);
1003 if Is_Non_Empty_List (Statements (P)) then
1004 Insert_List_Before_And_Analyze
1005 (First (Statements (P)), Post_Call);
1006 else
1007 Set_Statements (P, Post_Call);
1008 end if;
1009 end;
1011 -- Otherwise, normal case where N is in a statement sequence,
1012 -- just put the post-call stuff after the call statement.
1014 else
1015 Insert_Actions_After (N, Post_Call);
1016 end if;
1017 end if;
1019 -- The call node itself is re-analyzed in Expand_Call.
1021 end Expand_Actuals;
1023 -----------------
1024 -- Expand_Call --
1025 -----------------
1027 -- This procedure handles expansion of function calls and procedure call
1028 -- statements (i.e. it serves as the body for Expand_N_Function_Call and
1029 -- Expand_N_Procedure_Call_Statement. Processing for calls includes:
1031 -- Replace call to Raise_Exception by Raise_Exception always if possible
1032 -- Provide values of actuals for all formals in Extra_Formals list
1033 -- Replace "call" to enumeration literal function by literal itself
1034 -- Rewrite call to predefined operator as operator
1035 -- Replace actuals to in-out parameters that are numeric conversions,
1036 -- with explicit assignment to temporaries before and after the call.
1037 -- Remove optional actuals if First_Optional_Parameter specified.
1039 -- Note that the list of actuals has been filled with default expressions
1040 -- during semantic analysis of the call. Only the extra actuals required
1041 -- for the 'Constrained attribute and for accessibility checks are added
1042 -- at this point.
1044 procedure Expand_Call (N : Node_Id) is
1045 Loc : constant Source_Ptr := Sloc (N);
1046 Remote : constant Boolean := Is_Remote_Call (N);
1047 Subp : Entity_Id;
1048 Orig_Subp : Entity_Id := Empty;
1049 Parent_Subp : Entity_Id;
1050 Parent_Formal : Entity_Id;
1051 Actual : Node_Id;
1052 Formal : Entity_Id;
1053 Prev : Node_Id := Empty;
1054 Prev_Orig : Node_Id;
1055 Scop : Entity_Id;
1056 Extra_Actuals : List_Id := No_List;
1057 Cond : Node_Id;
1059 procedure Add_Actual_Parameter (Insert_Param : Node_Id);
1060 -- Adds one entry to the end of the actual parameter list. Used for
1061 -- default parameters and for extra actuals (for Extra_Formals).
1062 -- The argument is an N_Parameter_Association node.
1064 procedure Add_Extra_Actual (Expr : Node_Id; EF : Entity_Id);
1065 -- Adds an extra actual to the list of extra actuals. Expr
1066 -- is the expression for the value of the actual, EF is the
1067 -- entity for the extra formal.
1069 function Inherited_From_Formal (S : Entity_Id) return Entity_Id;
1070 -- Within an instance, a type derived from a non-tagged formal derived
1071 -- type inherits from the original parent, not from the actual. This is
1072 -- tested in 4723-003. The current derivation mechanism has the derived
1073 -- type inherit from the actual, which is only correct outside of the
1074 -- instance. If the subprogram is inherited, we test for this particular
1075 -- case through a convoluted tree traversal before setting the proper
1076 -- subprogram to be called.
1078 --------------------------
1079 -- Add_Actual_Parameter --
1080 --------------------------
1082 procedure Add_Actual_Parameter (Insert_Param : Node_Id) is
1083 Actual_Expr : constant Node_Id :=
1084 Explicit_Actual_Parameter (Insert_Param);
1086 begin
1087 -- Case of insertion is first named actual
1089 if No (Prev) or else
1090 Nkind (Parent (Prev)) /= N_Parameter_Association
1091 then
1092 Set_Next_Named_Actual (Insert_Param, First_Named_Actual (N));
1093 Set_First_Named_Actual (N, Actual_Expr);
1095 if No (Prev) then
1096 if not Present (Parameter_Associations (N)) then
1097 Set_Parameter_Associations (N, New_List);
1098 Append (Insert_Param, Parameter_Associations (N));
1099 end if;
1100 else
1101 Insert_After (Prev, Insert_Param);
1102 end if;
1104 -- Case of insertion is not first named actual
1106 else
1107 Set_Next_Named_Actual
1108 (Insert_Param, Next_Named_Actual (Parent (Prev)));
1109 Set_Next_Named_Actual (Parent (Prev), Actual_Expr);
1110 Append (Insert_Param, Parameter_Associations (N));
1111 end if;
1113 Prev := Actual_Expr;
1114 end Add_Actual_Parameter;
1116 ----------------------
1117 -- Add_Extra_Actual --
1118 ----------------------
1120 procedure Add_Extra_Actual (Expr : Node_Id; EF : Entity_Id) is
1121 Loc : constant Source_Ptr := Sloc (Expr);
1123 begin
1124 if Extra_Actuals = No_List then
1125 Extra_Actuals := New_List;
1126 Set_Parent (Extra_Actuals, N);
1127 end if;
1129 Append_To (Extra_Actuals,
1130 Make_Parameter_Association (Loc,
1131 Explicit_Actual_Parameter => Expr,
1132 Selector_Name =>
1133 Make_Identifier (Loc, Chars (EF))));
1135 Analyze_And_Resolve (Expr, Etype (EF));
1136 end Add_Extra_Actual;
1138 ---------------------------
1139 -- Inherited_From_Formal --
1140 ---------------------------
1142 function Inherited_From_Formal (S : Entity_Id) return Entity_Id is
1143 Par : Entity_Id;
1144 Gen_Par : Entity_Id;
1145 Gen_Prim : Elist_Id;
1146 Elmt : Elmt_Id;
1147 Indic : Node_Id;
1149 begin
1150 -- If the operation is inherited, it is attached to the corresponding
1151 -- type derivation. If the parent in the derivation is a generic
1152 -- actual, it is a subtype of the actual, and we have to recover the
1153 -- original derived type declaration to find the proper parent.
1155 if Nkind (Parent (S)) /= N_Full_Type_Declaration
1156 or else not Is_Derived_Type (Defining_Identifier (Parent (S)))
1157 or else Nkind (Type_Definition (Original_Node (Parent (S))))
1158 /= N_Derived_Type_Definition
1159 or else not In_Instance
1160 then
1161 return Empty;
1163 else
1164 Indic :=
1165 (Subtype_Indication
1166 (Type_Definition (Original_Node (Parent (S)))));
1168 if Nkind (Indic) = N_Subtype_Indication then
1169 Par := Entity (Subtype_Mark (Indic));
1170 else
1171 Par := Entity (Indic);
1172 end if;
1173 end if;
1175 if not Is_Generic_Actual_Type (Par)
1176 or else Is_Tagged_Type (Par)
1177 or else Nkind (Parent (Par)) /= N_Subtype_Declaration
1178 or else not In_Open_Scopes (Scope (Par))
1179 then
1180 return Empty;
1182 else
1183 Gen_Par := Generic_Parent_Type (Parent (Par));
1184 end if;
1186 -- If the generic parent type is still the generic type, this
1187 -- is a private formal, not a derived formal, and there are no
1188 -- operations inherited from the formal.
1190 if Nkind (Parent (Gen_Par)) = N_Formal_Type_Declaration then
1191 return Empty;
1192 end if;
1194 Gen_Prim := Collect_Primitive_Operations (Gen_Par);
1195 Elmt := First_Elmt (Gen_Prim);
1197 while Present (Elmt) loop
1198 if Chars (Node (Elmt)) = Chars (S) then
1199 declare
1200 F1 : Entity_Id;
1201 F2 : Entity_Id;
1202 begin
1204 F1 := First_Formal (S);
1205 F2 := First_Formal (Node (Elmt));
1207 while Present (F1)
1208 and then Present (F2)
1209 loop
1211 if Etype (F1) = Etype (F2)
1212 or else Etype (F2) = Gen_Par
1213 then
1214 Next_Formal (F1);
1215 Next_Formal (F2);
1216 else
1217 Next_Elmt (Elmt);
1218 exit; -- not the right subprogram
1219 end if;
1221 return Node (Elmt);
1222 end loop;
1223 end;
1225 else
1226 Next_Elmt (Elmt);
1227 end if;
1228 end loop;
1230 raise Program_Error;
1231 end Inherited_From_Formal;
1233 -- Start of processing for Expand_Call
1235 begin
1236 -- Ignore if previous error
1238 if Nkind (N) in N_Has_Etype and then Etype (N) = Any_Type then
1239 return;
1240 end if;
1242 -- Call using access to subprogram with explicit dereference
1244 if Nkind (Name (N)) = N_Explicit_Dereference then
1245 Subp := Etype (Name (N));
1246 Parent_Subp := Empty;
1248 -- Case of call to simple entry, where the Name is a selected component
1249 -- whose prefix is the task, and whose selector name is the entry name
1251 elsif Nkind (Name (N)) = N_Selected_Component then
1252 Subp := Entity (Selector_Name (Name (N)));
1253 Parent_Subp := Empty;
1255 -- Case of call to member of entry family, where Name is an indexed
1256 -- component, with the prefix being a selected component giving the
1257 -- task and entry family name, and the index being the entry index.
1259 elsif Nkind (Name (N)) = N_Indexed_Component then
1260 Subp := Entity (Selector_Name (Prefix (Name (N))));
1261 Parent_Subp := Empty;
1263 -- Normal case
1265 else
1266 Subp := Entity (Name (N));
1267 Parent_Subp := Alias (Subp);
1269 -- Replace call to Raise_Exception by call to Raise_Exception_Always
1270 -- if we can tell that the first parameter cannot possibly be null.
1271 -- This helps optimization and also generation of warnings.
1273 if not Restriction_Active (No_Exception_Handlers)
1274 and then Is_RTE (Subp, RE_Raise_Exception)
1275 then
1276 declare
1277 FA : constant Node_Id := Original_Node (First_Actual (N));
1279 begin
1280 -- The case we catch is where the first argument is obtained
1281 -- using the Identity attribute (which must always be non-null)
1283 if Nkind (FA) = N_Attribute_Reference
1284 and then Attribute_Name (FA) = Name_Identity
1285 then
1286 Subp := RTE (RE_Raise_Exception_Always);
1287 Set_Entity (Name (N), Subp);
1288 end if;
1289 end;
1290 end if;
1292 if Ekind (Subp) = E_Entry then
1293 Parent_Subp := Empty;
1294 end if;
1295 end if;
1297 -- First step, compute extra actuals, corresponding to any
1298 -- Extra_Formals present. Note that we do not access Extra_Formals
1299 -- directly, instead we simply note the presence of the extra
1300 -- formals as we process the regular formals and collect the
1301 -- corresponding actuals in Extra_Actuals.
1303 -- We also generate any required range checks for actuals as we go
1304 -- through the loop, since this is a convenient place to do this.
1306 Formal := First_Formal (Subp);
1307 Actual := First_Actual (N);
1308 while Present (Formal) loop
1310 -- Generate range check if required (not activated yet ???)
1312 -- if Do_Range_Check (Actual) then
1313 -- Set_Do_Range_Check (Actual, False);
1314 -- Generate_Range_Check
1315 -- (Actual, Etype (Formal), CE_Range_Check_Failed);
1316 -- end if;
1318 -- Prepare to examine current entry
1320 Prev := Actual;
1321 Prev_Orig := Original_Node (Prev);
1323 -- Create possible extra actual for constrained case. Usually,
1324 -- the extra actual is of the form actual'constrained, but since
1325 -- this attribute is only available for unconstrained records,
1326 -- TRUE is expanded if the type of the formal happens to be
1327 -- constrained (for instance when this procedure is inherited
1328 -- from an unconstrained record to a constrained one) or if the
1329 -- actual has no discriminant (its type is constrained). An
1330 -- exception to this is the case of a private type without
1331 -- discriminants. In this case we pass FALSE because the
1332 -- object has underlying discriminants with defaults.
1334 if Present (Extra_Constrained (Formal)) then
1335 if Ekind (Etype (Prev)) in Private_Kind
1336 and then not Has_Discriminants (Base_Type (Etype (Prev)))
1337 then
1338 Add_Extra_Actual (
1339 New_Occurrence_Of (Standard_False, Loc),
1340 Extra_Constrained (Formal));
1342 elsif Is_Constrained (Etype (Formal))
1343 or else not Has_Discriminants (Etype (Prev))
1344 then
1345 Add_Extra_Actual (
1346 New_Occurrence_Of (Standard_True, Loc),
1347 Extra_Constrained (Formal));
1349 else
1350 -- If the actual is a type conversion, then the constrained
1351 -- test applies to the actual, not the target type.
1353 declare
1354 Act_Prev : Node_Id := Prev;
1356 begin
1357 -- Test for unchecked conversions as well, which can
1358 -- occur as out parameter actuals on calls to stream
1359 -- procedures.
1361 while Nkind (Act_Prev) = N_Type_Conversion
1362 or else Nkind (Act_Prev) = N_Unchecked_Type_Conversion
1363 loop
1364 Act_Prev := Expression (Act_Prev);
1365 end loop;
1367 Add_Extra_Actual (
1368 Make_Attribute_Reference (Sloc (Prev),
1369 Prefix =>
1370 Duplicate_Subexpr_No_Checks
1371 (Act_Prev, Name_Req => True),
1372 Attribute_Name => Name_Constrained),
1373 Extra_Constrained (Formal));
1374 end;
1375 end if;
1376 end if;
1378 -- Create possible extra actual for accessibility level
1380 if Present (Extra_Accessibility (Formal)) then
1381 if Is_Entity_Name (Prev_Orig) then
1383 -- When passing an access parameter as the actual to another
1384 -- access parameter we need to pass along the actual's own
1385 -- associated access level parameter. This is done if we are
1386 -- in the scope of the formal access parameter (if this is an
1387 -- inlined body the extra formal is irrelevant).
1389 if Ekind (Entity (Prev_Orig)) in Formal_Kind
1390 and then Ekind (Etype (Prev_Orig)) = E_Anonymous_Access_Type
1391 and then In_Open_Scopes (Scope (Entity (Prev_Orig)))
1392 then
1393 declare
1394 Parm_Ent : constant Entity_Id := Param_Entity (Prev_Orig);
1396 begin
1397 pragma Assert (Present (Parm_Ent));
1399 if Present (Extra_Accessibility (Parm_Ent)) then
1400 Add_Extra_Actual (
1401 New_Occurrence_Of
1402 (Extra_Accessibility (Parm_Ent), Loc),
1403 Extra_Accessibility (Formal));
1405 -- If the actual access parameter does not have an
1406 -- associated extra formal providing its scope level,
1407 -- then treat the actual as having library-level
1408 -- accessibility.
1410 else
1411 Add_Extra_Actual (
1412 Make_Integer_Literal (Loc,
1413 Intval => Scope_Depth (Standard_Standard)),
1414 Extra_Accessibility (Formal));
1415 end if;
1416 end;
1418 -- The actual is a normal access value, so just pass the
1419 -- level of the actual's access type.
1421 else
1422 Add_Extra_Actual (
1423 Make_Integer_Literal (Loc,
1424 Intval => Type_Access_Level (Etype (Prev_Orig))),
1425 Extra_Accessibility (Formal));
1426 end if;
1428 else
1429 case Nkind (Prev_Orig) is
1431 when N_Attribute_Reference =>
1433 case Get_Attribute_Id (Attribute_Name (Prev_Orig)) is
1435 -- For X'Access, pass on the level of the prefix X
1437 when Attribute_Access =>
1438 Add_Extra_Actual (
1439 Make_Integer_Literal (Loc,
1440 Intval =>
1441 Object_Access_Level (Prefix (Prev_Orig))),
1442 Extra_Accessibility (Formal));
1444 -- Treat the unchecked attributes as library-level
1446 when Attribute_Unchecked_Access |
1447 Attribute_Unrestricted_Access =>
1448 Add_Extra_Actual (
1449 Make_Integer_Literal (Loc,
1450 Intval => Scope_Depth (Standard_Standard)),
1451 Extra_Accessibility (Formal));
1453 -- No other cases of attributes returning access
1454 -- values that can be passed to access parameters
1456 when others =>
1457 raise Program_Error;
1459 end case;
1461 -- For allocators we pass the level of the execution of
1462 -- the called subprogram, which is one greater than the
1463 -- current scope level.
1465 when N_Allocator =>
1466 Add_Extra_Actual (
1467 Make_Integer_Literal (Loc,
1468 Scope_Depth (Current_Scope) + 1),
1469 Extra_Accessibility (Formal));
1471 -- For other cases we simply pass the level of the
1472 -- actual's access type.
1474 when others =>
1475 Add_Extra_Actual (
1476 Make_Integer_Literal (Loc,
1477 Intval => Type_Access_Level (Etype (Prev_Orig))),
1478 Extra_Accessibility (Formal));
1480 end case;
1481 end if;
1482 end if;
1484 -- Perform the check of 4.6(49) that prevents a null value
1485 -- from being passed as an actual to an access parameter.
1486 -- Note that the check is elided in the common cases of
1487 -- passing an access attribute or access parameter as an
1488 -- actual. Also, we currently don't enforce this check for
1489 -- expander-generated actuals and when -gnatdj is set.
1491 if Ekind (Etype (Formal)) /= E_Anonymous_Access_Type
1492 or else Access_Checks_Suppressed (Subp)
1493 then
1494 null;
1496 elsif Debug_Flag_J then
1497 null;
1499 elsif not Comes_From_Source (Prev) then
1500 null;
1502 elsif Is_Entity_Name (Prev)
1503 and then Ekind (Etype (Prev)) = E_Anonymous_Access_Type
1504 then
1505 null;
1507 elsif Nkind (Prev) = N_Allocator
1508 or else Nkind (Prev) = N_Attribute_Reference
1509 then
1510 null;
1512 -- Suppress null checks when passing to access parameters
1513 -- of Java subprograms. (Should this be done for other
1514 -- foreign conventions as well ???)
1516 elsif Convention (Subp) = Convention_Java then
1517 null;
1519 -- Ada 0Y (AI-231): do not force the check in case of Ada 0Y unless
1520 -- it is a null-excluding type
1522 elsif not Extensions_Allowed
1523 or else Can_Never_Be_Null (Etype (Prev))
1524 then
1525 Cond :=
1526 Make_Op_Eq (Loc,
1527 Left_Opnd => Duplicate_Subexpr_No_Checks (Prev),
1528 Right_Opnd => Make_Null (Loc));
1529 Insert_Action (Prev,
1530 Make_Raise_Constraint_Error (Loc,
1531 Condition => Cond,
1532 Reason => CE_Access_Parameter_Is_Null));
1533 end if;
1535 -- Perform appropriate validity checks on parameters that
1536 -- are entities.
1538 if Validity_Checks_On then
1539 if Ekind (Formal) = E_In_Parameter
1540 and then Validity_Check_In_Params
1541 then
1542 -- If the actual is an indexed component of a packed
1543 -- type, it has not been expanded yet. It will be
1544 -- copied in the validity code that follows, and has
1545 -- to be expanded appropriately, so reanalyze it.
1547 if Nkind (Actual) = N_Indexed_Component then
1548 Set_Analyzed (Actual, False);
1549 end if;
1551 Ensure_Valid (Actual);
1553 elsif Ekind (Formal) = E_In_Out_Parameter
1554 and then Validity_Check_In_Out_Params
1555 then
1556 Ensure_Valid (Actual);
1557 end if;
1558 end if;
1560 -- For IN OUT and OUT parameters, ensure that subscripts are valid
1561 -- since this is a left side reference. We only do this for calls
1562 -- from the source program since we assume that compiler generated
1563 -- calls explicitly generate any required checks. We also need it
1564 -- only if we are doing standard validity checks, since clearly it
1565 -- is not needed if validity checks are off, and in subscript
1566 -- validity checking mode, all indexed components are checked with
1567 -- a call directly from Expand_N_Indexed_Component.
1569 if Comes_From_Source (N)
1570 and then Ekind (Formal) /= E_In_Parameter
1571 and then Validity_Checks_On
1572 and then Validity_Check_Default
1573 and then not Validity_Check_Subscripts
1574 then
1575 Check_Valid_Lvalue_Subscripts (Actual);
1576 end if;
1578 -- Mark any scalar OUT parameter that is a simple variable
1579 -- as no longer known to be valid (unless the type is always
1580 -- valid). This reflects the fact that if an OUT parameter
1581 -- is never set in a procedure, then it can become invalid
1582 -- on return from the procedure.
1584 if Ekind (Formal) = E_Out_Parameter
1585 and then Is_Entity_Name (Actual)
1586 and then Ekind (Entity (Actual)) = E_Variable
1587 and then not Is_Known_Valid (Etype (Actual))
1588 then
1589 Set_Is_Known_Valid (Entity (Actual), False);
1590 end if;
1592 -- For an OUT or IN OUT parameter of an access type, if the
1593 -- actual is an entity, then it is no longer known to be non-null.
1595 if Ekind (Formal) /= E_In_Parameter
1596 and then Is_Entity_Name (Actual)
1597 and then Is_Access_Type (Etype (Actual))
1598 then
1599 Set_Is_Known_Non_Null (Entity (Actual), False);
1600 end if;
1602 -- If the formal is class wide and the actual is an aggregate, force
1603 -- evaluation so that the back end who does not know about class-wide
1604 -- type, does not generate a temporary of the wrong size.
1606 if not Is_Class_Wide_Type (Etype (Formal)) then
1607 null;
1609 elsif Nkind (Actual) = N_Aggregate
1610 or else (Nkind (Actual) = N_Qualified_Expression
1611 and then Nkind (Expression (Actual)) = N_Aggregate)
1612 then
1613 Force_Evaluation (Actual);
1614 end if;
1616 -- In a remote call, if the formal is of a class-wide type, check
1617 -- that the actual meets the requirements described in E.4(18).
1619 if Remote
1620 and then Is_Class_Wide_Type (Etype (Formal))
1621 then
1622 Insert_Action (Actual,
1623 Make_Implicit_If_Statement (N,
1624 Condition =>
1625 Make_Op_Not (Loc,
1626 Get_Remotely_Callable
1627 (Duplicate_Subexpr_Move_Checks (Actual))),
1628 Then_Statements => New_List (
1629 Make_Procedure_Call_Statement (Loc,
1630 New_Occurrence_Of (RTE
1631 (RE_Raise_Program_Error_For_E_4_18), Loc)))));
1632 end if;
1634 Next_Actual (Actual);
1635 Next_Formal (Formal);
1636 end loop;
1638 -- If we are expanding a rhs of an assignement we need to check if
1639 -- tag propagation is needed. This code belongs theorically in Analyze
1640 -- Assignment but has to be done earlier (bottom-up) because the
1641 -- assignment might be transformed into a declaration for an uncons-
1642 -- trained value, if the expression is classwide.
1644 if Nkind (N) = N_Function_Call
1645 and then Is_Tag_Indeterminate (N)
1646 and then Is_Entity_Name (Name (N))
1647 then
1648 declare
1649 Ass : Node_Id := Empty;
1651 begin
1652 if Nkind (Parent (N)) = N_Assignment_Statement then
1653 Ass := Parent (N);
1655 elsif Nkind (Parent (N)) = N_Qualified_Expression
1656 and then Nkind (Parent (Parent (N))) = N_Assignment_Statement
1657 then
1658 Ass := Parent (Parent (N));
1659 end if;
1661 if Present (Ass)
1662 and then Is_Class_Wide_Type (Etype (Name (Ass)))
1663 then
1664 if Etype (N) /= Root_Type (Etype (Name (Ass))) then
1665 Error_Msg_NE
1666 ("tag-indeterminate expression must have type&"
1667 & "('R'M 5.2 (6))", N, Root_Type (Etype (Name (Ass))));
1668 else
1669 Propagate_Tag (Name (Ass), N);
1670 end if;
1672 -- The call will be rewritten as a dispatching call, and
1673 -- expanded as such.
1675 return;
1676 end if;
1677 end;
1678 end if;
1680 -- Deals with Dispatch_Call if we still have a call, before expanding
1681 -- extra actuals since this will be done on the re-analysis of the
1682 -- dispatching call. Note that we do not try to shorten the actual
1683 -- list for a dispatching call, it would not make sense to do so.
1684 -- Expansion of dispatching calls is suppressed when Java_VM, because
1685 -- the JVM back end directly handles the generation of dispatching
1686 -- calls and would have to undo any expansion to an indirect call.
1688 if (Nkind (N) = N_Function_Call
1689 or else Nkind (N) = N_Procedure_Call_Statement)
1690 and then Present (Controlling_Argument (N))
1691 and then not Java_VM
1692 then
1693 Expand_Dispatch_Call (N);
1695 -- The following return is worrisome. Is it really OK to
1696 -- skip all remaining processing in this procedure ???
1698 return;
1700 -- Similarly, expand calls to RCI subprograms on which pragma
1701 -- All_Calls_Remote applies. The rewriting will be reanalyzed
1702 -- later. Do this only when the call comes from source since we do
1703 -- not want such a rewritting to occur in expanded code.
1705 elsif Is_All_Remote_Call (N) then
1706 Expand_All_Calls_Remote_Subprogram_Call (N);
1708 -- Similarly, do not add extra actuals for an entry call whose entity
1709 -- is a protected procedure, or for an internal protected subprogram
1710 -- call, because it will be rewritten as a protected subprogram call
1711 -- and reanalyzed (see Expand_Protected_Subprogram_Call).
1713 elsif Is_Protected_Type (Scope (Subp))
1714 and then (Ekind (Subp) = E_Procedure
1715 or else Ekind (Subp) = E_Function)
1716 then
1717 null;
1719 -- During that loop we gathered the extra actuals (the ones that
1720 -- correspond to Extra_Formals), so now they can be appended.
1722 else
1723 while Is_Non_Empty_List (Extra_Actuals) loop
1724 Add_Actual_Parameter (Remove_Head (Extra_Actuals));
1725 end loop;
1726 end if;
1728 if Ekind (Subp) = E_Procedure
1729 or else (Ekind (Subp) = E_Subprogram_Type
1730 and then Etype (Subp) = Standard_Void_Type)
1731 or else Is_Entry (Subp)
1732 then
1733 Expand_Actuals (N, Subp);
1734 end if;
1736 -- If the subprogram is a renaming, or if it is inherited, replace it
1737 -- in the call with the name of the actual subprogram being called.
1738 -- If this is a dispatching call, the run-time decides what to call.
1739 -- The Alias attribute does not apply to entries.
1741 if Nkind (N) /= N_Entry_Call_Statement
1742 and then No (Controlling_Argument (N))
1743 and then Present (Parent_Subp)
1744 then
1745 if Present (Inherited_From_Formal (Subp)) then
1746 Parent_Subp := Inherited_From_Formal (Subp);
1747 else
1748 while Present (Alias (Parent_Subp)) loop
1749 Parent_Subp := Alias (Parent_Subp);
1750 end loop;
1751 end if;
1753 Set_Entity (Name (N), Parent_Subp);
1755 if Is_Abstract (Parent_Subp)
1756 and then not In_Instance
1757 then
1758 Error_Msg_NE
1759 ("cannot call abstract subprogram &!", Name (N), Parent_Subp);
1760 end if;
1762 -- Add an explicit conversion for parameter of the derived type.
1763 -- This is only done for scalar and access in-parameters. Others
1764 -- have been expanded in expand_actuals.
1766 Formal := First_Formal (Subp);
1767 Parent_Formal := First_Formal (Parent_Subp);
1768 Actual := First_Actual (N);
1770 -- It is not clear that conversion is needed for intrinsic
1771 -- subprograms, but it certainly is for those that are user-
1772 -- defined, and that can be inherited on derivation, namely
1773 -- unchecked conversion and deallocation.
1774 -- General case needs study ???
1776 if not Is_Intrinsic_Subprogram (Parent_Subp)
1777 or else Is_Generic_Instance (Parent_Subp)
1778 then
1779 while Present (Formal) loop
1781 if Etype (Formal) /= Etype (Parent_Formal)
1782 and then Is_Scalar_Type (Etype (Formal))
1783 and then Ekind (Formal) = E_In_Parameter
1784 and then not Raises_Constraint_Error (Actual)
1785 then
1786 Rewrite (Actual,
1787 OK_Convert_To (Etype (Parent_Formal),
1788 Relocate_Node (Actual)));
1790 Analyze (Actual);
1791 Resolve (Actual, Etype (Parent_Formal));
1792 Enable_Range_Check (Actual);
1794 elsif Is_Access_Type (Etype (Formal))
1795 and then Base_Type (Etype (Parent_Formal))
1796 /= Base_Type (Etype (Actual))
1797 then
1798 if Ekind (Formal) /= E_In_Parameter then
1799 Rewrite (Actual,
1800 Convert_To (Etype (Parent_Formal),
1801 Relocate_Node (Actual)));
1803 Analyze (Actual);
1804 Resolve (Actual, Etype (Parent_Formal));
1806 elsif
1807 Ekind (Etype (Parent_Formal)) = E_Anonymous_Access_Type
1808 and then Designated_Type (Etype (Parent_Formal))
1810 Designated_Type (Etype (Actual))
1811 and then not Is_Controlling_Formal (Formal)
1812 then
1813 -- This unchecked conversion is not necessary unless
1814 -- inlining is enabled, because in that case the type
1815 -- mismatch may become visible in the body about to be
1816 -- inlined.
1818 Rewrite (Actual,
1819 Unchecked_Convert_To (Etype (Parent_Formal),
1820 Relocate_Node (Actual)));
1822 Analyze (Actual);
1823 Resolve (Actual, Etype (Parent_Formal));
1824 end if;
1825 end if;
1827 Next_Formal (Formal);
1828 Next_Formal (Parent_Formal);
1829 Next_Actual (Actual);
1830 end loop;
1831 end if;
1833 Orig_Subp := Subp;
1834 Subp := Parent_Subp;
1835 end if;
1837 if Is_RTE (Subp, RE_Abort_Task) then
1838 Check_Restriction (No_Abort_Statements, N);
1839 end if;
1841 if Nkind (Name (N)) = N_Explicit_Dereference then
1843 -- Handle case of access to protected subprogram type
1845 if Ekind (Base_Type (Etype (Prefix (Name (N))))) =
1846 E_Access_Protected_Subprogram_Type
1847 then
1848 -- If this is a call through an access to protected operation,
1849 -- the prefix has the form (object'address, operation'access).
1850 -- Rewrite as a for other protected calls: the object is the
1851 -- first parameter of the list of actuals.
1853 declare
1854 Call : Node_Id;
1855 Parm : List_Id;
1856 Nam : Node_Id;
1857 Obj : Node_Id;
1858 Ptr : constant Node_Id := Prefix (Name (N));
1860 T : constant Entity_Id :=
1861 Equivalent_Type (Base_Type (Etype (Ptr)));
1863 D_T : constant Entity_Id :=
1864 Designated_Type (Base_Type (Etype (Ptr)));
1866 begin
1867 Obj := Make_Selected_Component (Loc,
1868 Prefix => Unchecked_Convert_To (T, Ptr),
1869 Selector_Name => New_Occurrence_Of (First_Entity (T), Loc));
1871 Nam := Make_Selected_Component (Loc,
1872 Prefix => Unchecked_Convert_To (T, Ptr),
1873 Selector_Name => New_Occurrence_Of (
1874 Next_Entity (First_Entity (T)), Loc));
1876 Nam := Make_Explicit_Dereference (Loc, Nam);
1878 if Present (Parameter_Associations (N)) then
1879 Parm := Parameter_Associations (N);
1880 else
1881 Parm := New_List;
1882 end if;
1884 Prepend (Obj, Parm);
1886 if Etype (D_T) = Standard_Void_Type then
1887 Call := Make_Procedure_Call_Statement (Loc,
1888 Name => Nam,
1889 Parameter_Associations => Parm);
1890 else
1891 Call := Make_Function_Call (Loc,
1892 Name => Nam,
1893 Parameter_Associations => Parm);
1894 end if;
1896 Set_First_Named_Actual (Call, First_Named_Actual (N));
1897 Set_Etype (Call, Etype (D_T));
1899 -- We do not re-analyze the call to avoid infinite recursion.
1900 -- We analyze separately the prefix and the object, and set
1901 -- the checks on the prefix that would otherwise be emitted
1902 -- when resolving a call.
1904 Rewrite (N, Call);
1905 Analyze (Nam);
1906 Apply_Access_Check (Nam);
1907 Analyze (Obj);
1908 return;
1909 end;
1910 end if;
1911 end if;
1913 -- If this is a call to an intrinsic subprogram, then perform the
1914 -- appropriate expansion to the corresponding tree node and we
1915 -- are all done (since after that the call is gone!)
1917 if Is_Intrinsic_Subprogram (Subp) then
1918 Expand_Intrinsic_Call (N, Subp);
1919 return;
1920 end if;
1922 if Ekind (Subp) = E_Function
1923 or else Ekind (Subp) = E_Procedure
1924 then
1925 if Is_Inlined (Subp) then
1927 Inlined_Subprogram : declare
1928 Bod : Node_Id;
1929 Must_Inline : Boolean := False;
1930 Spec : constant Node_Id := Unit_Declaration_Node (Subp);
1931 Scop : constant Entity_Id := Scope (Subp);
1933 function In_Unfrozen_Instance return Boolean;
1934 -- If the subprogram comes from an instance in the same
1935 -- unit, and the instance is not yet frozen, inlining might
1936 -- trigger order-of-elaboration problems in gigi.
1938 --------------------------
1939 -- In_Unfrozen_Instance --
1940 --------------------------
1942 function In_Unfrozen_Instance return Boolean is
1943 S : Entity_Id := Scop;
1945 begin
1946 while Present (S)
1947 and then S /= Standard_Standard
1948 loop
1949 if Is_Generic_Instance (S)
1950 and then Present (Freeze_Node (S))
1951 and then not Analyzed (Freeze_Node (S))
1952 then
1953 return True;
1954 end if;
1956 S := Scope (S);
1957 end loop;
1959 return False;
1960 end In_Unfrozen_Instance;
1962 -- Start of processing for Inlined_Subprogram
1964 begin
1965 -- Verify that the body to inline has already been seen,
1966 -- and that if the body is in the current unit the inlining
1967 -- does not occur earlier. This avoids order-of-elaboration
1968 -- problems in gigi.
1970 if No (Spec)
1971 or else Nkind (Spec) /= N_Subprogram_Declaration
1972 or else No (Body_To_Inline (Spec))
1973 then
1974 Must_Inline := False;
1976 -- If this an inherited function that returns a private
1977 -- type, do not inline if the full view is an unconstrained
1978 -- array, because such calls cannot be inlined.
1980 elsif Present (Orig_Subp)
1981 and then Is_Array_Type (Etype (Orig_Subp))
1982 and then not Is_Constrained (Etype (Orig_Subp))
1983 then
1984 Must_Inline := False;
1986 elsif In_Unfrozen_Instance then
1987 Must_Inline := False;
1989 else
1990 Bod := Body_To_Inline (Spec);
1992 if (In_Extended_Main_Code_Unit (N)
1993 or else In_Extended_Main_Code_Unit (Parent (N))
1994 or else Is_Always_Inlined (Subp))
1995 and then (not In_Same_Extended_Unit (Sloc (Bod), Loc)
1996 or else
1997 Earlier_In_Extended_Unit (Sloc (Bod), Loc))
1998 then
1999 Must_Inline := True;
2001 -- If we are compiling a package body that is not the main
2002 -- unit, it must be for inlining/instantiation purposes,
2003 -- in which case we inline the call to insure that the same
2004 -- temporaries are generated when compiling the body by
2005 -- itself. Otherwise link errors can occur.
2007 -- If the function being called is itself in the main unit,
2008 -- we cannot inline, because there is a risk of double
2009 -- elaboration and/or circularity: the inlining can make
2010 -- visible a private entity in the body of the main unit,
2011 -- that gigi will see before its sees its proper definition.
2013 elsif not (In_Extended_Main_Code_Unit (N))
2014 and then In_Package_Body
2015 then
2016 Must_Inline := not In_Extended_Main_Source_Unit (Subp);
2017 end if;
2018 end if;
2020 if Must_Inline then
2021 Expand_Inlined_Call (N, Subp, Orig_Subp);
2023 else
2024 -- Let the back end handle it
2026 Add_Inlined_Body (Subp);
2028 if Front_End_Inlining
2029 and then Nkind (Spec) = N_Subprogram_Declaration
2030 and then (In_Extended_Main_Code_Unit (N))
2031 and then No (Body_To_Inline (Spec))
2032 and then not Has_Completion (Subp)
2033 and then In_Same_Extended_Unit (Sloc (Spec), Loc)
2034 then
2035 Cannot_Inline
2036 ("cannot inline& (body not seen yet)?",
2037 N, Subp);
2038 end if;
2039 end if;
2040 end Inlined_Subprogram;
2041 end if;
2042 end if;
2044 -- Check for a protected subprogram. This is either an intra-object
2045 -- call, or a protected function call. Protected procedure calls are
2046 -- rewritten as entry calls and handled accordingly.
2048 Scop := Scope (Subp);
2050 if Nkind (N) /= N_Entry_Call_Statement
2051 and then Is_Protected_Type (Scop)
2052 then
2053 -- If the call is an internal one, it is rewritten as a call to
2054 -- to the corresponding unprotected subprogram.
2056 Expand_Protected_Subprogram_Call (N, Subp, Scop);
2057 end if;
2059 -- Functions returning controlled objects need special attention
2061 if Controlled_Type (Etype (Subp))
2062 and then not Is_Return_By_Reference_Type (Etype (Subp))
2063 then
2064 Expand_Ctrl_Function_Call (N);
2065 end if;
2067 -- Test for First_Optional_Parameter, and if so, truncate parameter
2068 -- list if there are optional parameters at the trailing end.
2069 -- Note we never delete procedures for call via a pointer.
2071 if (Ekind (Subp) = E_Procedure or else Ekind (Subp) = E_Function)
2072 and then Present (First_Optional_Parameter (Subp))
2073 then
2074 declare
2075 Last_Keep_Arg : Node_Id;
2077 begin
2078 -- Last_Keep_Arg will hold the last actual that should be
2079 -- retained. If it remains empty at the end, it means that
2080 -- all parameters are optional.
2082 Last_Keep_Arg := Empty;
2084 -- Find first optional parameter, must be present since we
2085 -- checked the validity of the parameter before setting it.
2087 Formal := First_Formal (Subp);
2088 Actual := First_Actual (N);
2089 while Formal /= First_Optional_Parameter (Subp) loop
2090 Last_Keep_Arg := Actual;
2091 Next_Formal (Formal);
2092 Next_Actual (Actual);
2093 end loop;
2095 -- We have Formal and Actual pointing to the first potentially
2096 -- droppable argument. We can drop all the trailing arguments
2097 -- whose actual matches the default. Note that we know that all
2098 -- remaining formals have defaults, because we checked that this
2099 -- requirement was met before setting First_Optional_Parameter.
2101 -- We use Fully_Conformant_Expressions to check for identity
2102 -- between formals and actuals, which may miss some cases, but
2103 -- on the other hand, this is only an optimization (if we fail
2104 -- to truncate a parameter it does not affect functionality).
2105 -- So if the default is 3 and the actual is 1+2, we consider
2106 -- them unequal, which hardly seems worrisome.
2108 while Present (Formal) loop
2109 if not Fully_Conformant_Expressions
2110 (Actual, Default_Value (Formal))
2111 then
2112 Last_Keep_Arg := Actual;
2113 end if;
2115 Next_Formal (Formal);
2116 Next_Actual (Actual);
2117 end loop;
2119 -- If no arguments, delete entire list, this is the easy case
2121 if No (Last_Keep_Arg) then
2122 while Is_Non_Empty_List (Parameter_Associations (N)) loop
2123 Delete_Tree (Remove_Head (Parameter_Associations (N)));
2124 end loop;
2126 Set_Parameter_Associations (N, No_List);
2127 Set_First_Named_Actual (N, Empty);
2129 -- Case where at the last retained argument is positional. This
2130 -- is also an easy case, since the retained arguments are already
2131 -- in the right form, and we don't need to worry about the order
2132 -- of arguments that get eliminated.
2134 elsif Is_List_Member (Last_Keep_Arg) then
2135 while Present (Next (Last_Keep_Arg)) loop
2136 Delete_Tree (Remove_Next (Last_Keep_Arg));
2137 end loop;
2139 Set_First_Named_Actual (N, Empty);
2141 -- This is the annoying case where the last retained argument
2142 -- is a named parameter. Since the original arguments are not
2143 -- in declaration order, we may have to delete some fairly
2144 -- random collection of arguments.
2146 else
2147 declare
2148 Temp : Node_Id;
2149 Passoc : Node_Id;
2151 Discard : Node_Id;
2152 pragma Warnings (Off, Discard);
2154 begin
2155 -- First step, remove all the named parameters from the
2156 -- list (they are still chained using First_Named_Actual
2157 -- and Next_Named_Actual, so we have not lost them!)
2159 Temp := First (Parameter_Associations (N));
2161 -- Case of all parameters named, remove them all
2163 if Nkind (Temp) = N_Parameter_Association then
2164 while Is_Non_Empty_List (Parameter_Associations (N)) loop
2165 Temp := Remove_Head (Parameter_Associations (N));
2166 end loop;
2168 -- Case of mixed positional/named, remove named parameters
2170 else
2171 while Nkind (Next (Temp)) /= N_Parameter_Association loop
2172 Next (Temp);
2173 end loop;
2175 while Present (Next (Temp)) loop
2176 Discard := Remove_Next (Temp);
2177 end loop;
2178 end if;
2180 -- Now we loop through the named parameters, till we get
2181 -- to the last one to be retained, adding them to the list.
2182 -- Note that the Next_Named_Actual list does not need to be
2183 -- touched since we are only reordering them on the actual
2184 -- parameter association list.
2186 Passoc := Parent (First_Named_Actual (N));
2187 loop
2188 Temp := Relocate_Node (Passoc);
2189 Append_To
2190 (Parameter_Associations (N), Temp);
2191 exit when
2192 Last_Keep_Arg = Explicit_Actual_Parameter (Passoc);
2193 Passoc := Parent (Next_Named_Actual (Passoc));
2194 end loop;
2196 Set_Next_Named_Actual (Temp, Empty);
2198 loop
2199 Temp := Next_Named_Actual (Passoc);
2200 exit when No (Temp);
2201 Set_Next_Named_Actual
2202 (Passoc, Next_Named_Actual (Parent (Temp)));
2203 Delete_Tree (Temp);
2204 end loop;
2205 end;
2206 end if;
2207 end;
2208 end if;
2209 end Expand_Call;
2211 --------------------------
2212 -- Expand_Inlined_Call --
2213 --------------------------
2215 procedure Expand_Inlined_Call
2216 (N : Node_Id;
2217 Subp : Entity_Id;
2218 Orig_Subp : Entity_Id)
2220 Loc : constant Source_Ptr := Sloc (N);
2221 Is_Predef : constant Boolean :=
2222 Is_Predefined_File_Name
2223 (Unit_File_Name (Get_Source_Unit (Subp)));
2224 Orig_Bod : constant Node_Id :=
2225 Body_To_Inline (Unit_Declaration_Node (Subp));
2227 Blk : Node_Id;
2228 Bod : Node_Id;
2229 Decl : Node_Id;
2230 Exit_Lab : Entity_Id := Empty;
2231 F : Entity_Id;
2232 A : Node_Id;
2233 Lab_Decl : Node_Id;
2234 Lab_Id : Node_Id;
2235 New_A : Node_Id;
2236 Num_Ret : Int := 0;
2237 Ret_Type : Entity_Id;
2238 Targ : Node_Id;
2239 Temp : Entity_Id;
2240 Temp_Typ : Entity_Id;
2242 procedure Make_Exit_Label;
2243 -- Build declaration for exit label to be used in Return statements.
2245 function Process_Formals (N : Node_Id) return Traverse_Result;
2246 -- Replace occurrence of a formal with the corresponding actual, or
2247 -- the thunk generated for it.
2249 function Process_Sloc (Nod : Node_Id) return Traverse_Result;
2250 -- If the call being expanded is that of an internal subprogram,
2251 -- set the sloc of the generated block to that of the call itself,
2252 -- so that the expansion is skipped by the -next- command in gdb.
2253 -- Same processing for a subprogram in a predefined file, e.g.
2254 -- Ada.Tags. If Debug_Generated_Code is true, suppress this change
2255 -- to simplify our own development.
2257 procedure Rewrite_Function_Call (N : Node_Id; Blk : Node_Id);
2258 -- If the function body is a single expression, replace call with
2259 -- expression, else insert block appropriately.
2261 procedure Rewrite_Procedure_Call (N : Node_Id; Blk : Node_Id);
2262 -- If procedure body has no local variables, inline body without
2263 -- creating block, otherwise rewrite call with block.
2265 ---------------------
2266 -- Make_Exit_Label --
2267 ---------------------
2269 procedure Make_Exit_Label is
2270 begin
2271 -- Create exit label for subprogram, if one doesn't exist yet.
2273 if No (Exit_Lab) then
2274 Lab_Id := Make_Identifier (Loc, New_Internal_Name ('L'));
2275 Set_Entity (Lab_Id,
2276 Make_Defining_Identifier (Loc, Chars (Lab_Id)));
2277 Exit_Lab := Make_Label (Loc, Lab_Id);
2279 Lab_Decl :=
2280 Make_Implicit_Label_Declaration (Loc,
2281 Defining_Identifier => Entity (Lab_Id),
2282 Label_Construct => Exit_Lab);
2283 end if;
2284 end Make_Exit_Label;
2286 ---------------------
2287 -- Process_Formals --
2288 ---------------------
2290 function Process_Formals (N : Node_Id) return Traverse_Result is
2291 A : Entity_Id;
2292 E : Entity_Id;
2293 Ret : Node_Id;
2295 begin
2296 if Is_Entity_Name (N)
2297 and then Present (Entity (N))
2298 then
2299 E := Entity (N);
2301 if Is_Formal (E)
2302 and then Scope (E) = Subp
2303 then
2304 A := Renamed_Object (E);
2306 if Is_Entity_Name (A) then
2307 Rewrite (N, New_Occurrence_Of (Entity (A), Loc));
2309 elsif Nkind (A) = N_Defining_Identifier then
2310 Rewrite (N, New_Occurrence_Of (A, Loc));
2312 else -- numeric literal
2313 Rewrite (N, New_Copy (A));
2314 end if;
2315 end if;
2317 return Skip;
2319 elsif Nkind (N) = N_Return_Statement then
2321 if No (Expression (N)) then
2322 Make_Exit_Label;
2323 Rewrite (N, Make_Goto_Statement (Loc,
2324 Name => New_Copy (Lab_Id)));
2326 else
2327 if Nkind (Parent (N)) = N_Handled_Sequence_Of_Statements
2328 and then Nkind (Parent (Parent (N))) = N_Subprogram_Body
2329 then
2330 -- Function body is a single expression. No need for
2331 -- exit label.
2333 null;
2335 else
2336 Num_Ret := Num_Ret + 1;
2337 Make_Exit_Label;
2338 end if;
2340 -- Because of the presence of private types, the views of the
2341 -- expression and the context may be different, so place an
2342 -- unchecked conversion to the context type to avoid spurious
2343 -- errors, eg. when the expression is a numeric literal and
2344 -- the context is private. If the expression is an aggregate,
2345 -- use a qualified expression, because an aggregate is not a
2346 -- legal argument of a conversion.
2348 if Nkind (Expression (N)) = N_Aggregate
2349 or else Nkind (Expression (N)) = N_Null
2350 then
2351 Ret :=
2352 Make_Qualified_Expression (Sloc (N),
2353 Subtype_Mark => New_Occurrence_Of (Ret_Type, Sloc (N)),
2354 Expression => Relocate_Node (Expression (N)));
2355 else
2356 Ret :=
2357 Unchecked_Convert_To
2358 (Ret_Type, Relocate_Node (Expression (N)));
2359 end if;
2361 if Nkind (Targ) = N_Defining_Identifier then
2362 Rewrite (N,
2363 Make_Assignment_Statement (Loc,
2364 Name => New_Occurrence_Of (Targ, Loc),
2365 Expression => Ret));
2366 else
2367 Rewrite (N,
2368 Make_Assignment_Statement (Loc,
2369 Name => New_Copy (Targ),
2370 Expression => Ret));
2371 end if;
2373 Set_Assignment_OK (Name (N));
2375 if Present (Exit_Lab) then
2376 Insert_After (N,
2377 Make_Goto_Statement (Loc,
2378 Name => New_Copy (Lab_Id)));
2379 end if;
2380 end if;
2382 return OK;
2384 -- Remove pragma Unreferenced since it may refer to formals that
2385 -- are not visible in the inlined body, and in any case we will
2386 -- not be posting warnings on the inlined body so it is unneeded.
2388 elsif Nkind (N) = N_Pragma
2389 and then Chars (N) = Name_Unreferenced
2390 then
2391 Rewrite (N, Make_Null_Statement (Sloc (N)));
2392 return OK;
2394 else
2395 return OK;
2396 end if;
2397 end Process_Formals;
2399 procedure Replace_Formals is new Traverse_Proc (Process_Formals);
2401 ------------------
2402 -- Process_Sloc --
2403 ------------------
2405 function Process_Sloc (Nod : Node_Id) return Traverse_Result is
2406 begin
2407 if not Debug_Generated_Code then
2408 Set_Sloc (Nod, Sloc (N));
2409 Set_Comes_From_Source (Nod, False);
2410 end if;
2412 return OK;
2413 end Process_Sloc;
2415 procedure Reset_Slocs is new Traverse_Proc (Process_Sloc);
2417 ---------------------------
2418 -- Rewrite_Function_Call --
2419 ---------------------------
2421 procedure Rewrite_Function_Call (N : Node_Id; Blk : Node_Id) is
2422 HSS : constant Node_Id := Handled_Statement_Sequence (Blk);
2423 Fst : constant Node_Id := First (Statements (HSS));
2425 begin
2426 -- Optimize simple case: function body is a single return statement,
2427 -- which has been expanded into an assignment.
2429 if Is_Empty_List (Declarations (Blk))
2430 and then Nkind (Fst) = N_Assignment_Statement
2431 and then No (Next (Fst))
2432 then
2434 -- The function call may have been rewritten as the temporary
2435 -- that holds the result of the call, in which case remove the
2436 -- now useless declaration.
2438 if Nkind (N) = N_Identifier
2439 and then Nkind (Parent (Entity (N))) = N_Object_Declaration
2440 then
2441 Rewrite (Parent (Entity (N)), Make_Null_Statement (Loc));
2442 end if;
2444 Rewrite (N, Expression (Fst));
2446 elsif Nkind (N) = N_Identifier
2447 and then Nkind (Parent (Entity (N))) = N_Object_Declaration
2448 then
2450 -- The block assigns the result of the call to the temporary.
2452 Insert_After (Parent (Entity (N)), Blk);
2454 elsif Nkind (Parent (N)) = N_Assignment_Statement
2455 and then Is_Entity_Name (Name (Parent (N)))
2456 then
2458 -- Replace assignment with the block
2460 declare
2461 Original_Assignment : constant Node_Id := Parent (N);
2462 Saved_Assignment : constant Node_Id :=
2463 Relocate_Node (Original_Assignment);
2464 pragma Warnings (Off, Saved_Assignment);
2465 -- Preserve the original assignment node to keep the
2466 -- complete assignment subtree consistent enough for
2467 -- Analyze_Assignment to proceed. We do not use the
2468 -- saved value, the point was just to do the relocation.
2469 -- We cannot rely on Original_Node to go back from the
2470 -- block node to the assignment node, because the
2471 -- assignment might already be a rewrite substitution.
2473 begin
2474 Rewrite (Original_Assignment, Blk);
2475 end;
2477 elsif Nkind (Parent (N)) = N_Object_Declaration then
2478 Set_Expression (Parent (N), Empty);
2479 Insert_After (Parent (N), Blk);
2480 end if;
2481 end Rewrite_Function_Call;
2483 ----------------------------
2484 -- Rewrite_Procedure_Call --
2485 ----------------------------
2487 procedure Rewrite_Procedure_Call (N : Node_Id; Blk : Node_Id) is
2488 HSS : constant Node_Id := Handled_Statement_Sequence (Blk);
2489 begin
2490 if Is_Empty_List (Declarations (Blk)) then
2491 Insert_List_After (N, Statements (HSS));
2492 Rewrite (N, Make_Null_Statement (Loc));
2493 else
2494 Rewrite (N, Blk);
2495 end if;
2496 end Rewrite_Procedure_Call;
2498 -- Start of processing for Expand_Inlined_Call
2500 begin
2501 -- Check for special case of To_Address call, and if so, just
2502 -- do an unchecked conversion instead of expanding the call.
2503 -- Not only is this more efficient, but it also avoids a
2504 -- problem with order of elaboration when address clauses
2505 -- are inlined (address expr elaborated at wrong point).
2507 if Subp = RTE (RE_To_Address) then
2508 Rewrite (N,
2509 Unchecked_Convert_To
2510 (RTE (RE_Address),
2511 Relocate_Node (First_Actual (N))));
2512 return;
2513 end if;
2515 if Nkind (Orig_Bod) = N_Defining_Identifier then
2517 -- Subprogram is a renaming_as_body. Calls appearing after the
2518 -- renaming can be replaced with calls to the renamed entity
2519 -- directly, because the subprograms are subtype conformant.
2521 Set_Name (N, New_Occurrence_Of (Orig_Bod, Loc));
2522 return;
2523 end if;
2525 -- Use generic machinery to copy body of inlined subprogram, as if it
2526 -- were an instantiation, resetting source locations appropriately, so
2527 -- that nested inlined calls appear in the main unit.
2529 Save_Env (Subp, Empty);
2530 Set_Copied_Sloc_For_Inlined_Body (N, Defining_Entity (Orig_Bod));
2532 Bod := Copy_Generic_Node (Orig_Bod, Empty, Instantiating => True);
2533 Blk :=
2534 Make_Block_Statement (Loc,
2535 Declarations => Declarations (Bod),
2536 Handled_Statement_Sequence => Handled_Statement_Sequence (Bod));
2538 if No (Declarations (Bod)) then
2539 Set_Declarations (Blk, New_List);
2540 end if;
2542 -- If this is a derived function, establish the proper return type.
2544 if Present (Orig_Subp)
2545 and then Orig_Subp /= Subp
2546 then
2547 Ret_Type := Etype (Orig_Subp);
2548 else
2549 Ret_Type := Etype (Subp);
2550 end if;
2552 F := First_Formal (Subp);
2553 A := First_Actual (N);
2555 -- Create temporaries for the actuals that are expressions, or that
2556 -- are scalars and require copying to preserve semantics.
2558 while Present (F) loop
2559 if Present (Renamed_Object (F)) then
2560 Error_Msg_N (" cannot inline call to recursive subprogram", N);
2561 return;
2562 end if;
2564 -- If the argument may be a controlling argument in a call within
2565 -- the inlined body, we must preserve its classwide nature to
2566 -- insure that dynamic dispatching take place subsequently.
2567 -- If the formal has a constraint it must be preserved to retain
2568 -- the semantics of the body.
2570 if Is_Class_Wide_Type (Etype (F))
2571 or else (Is_Access_Type (Etype (F))
2572 and then
2573 Is_Class_Wide_Type (Designated_Type (Etype (F))))
2574 then
2575 Temp_Typ := Etype (F);
2577 elsif Base_Type (Etype (F)) = Base_Type (Etype (A))
2578 and then Etype (F) /= Base_Type (Etype (F))
2579 then
2580 Temp_Typ := Etype (F);
2582 else
2583 Temp_Typ := Etype (A);
2584 end if;
2586 -- If the actual is a simple name or a literal, no need to
2587 -- create a temporary, object can be used directly.
2589 if (Is_Entity_Name (A)
2590 and then
2591 (not Is_Scalar_Type (Etype (A))
2592 or else Ekind (Entity (A)) = E_Enumeration_Literal))
2594 or else Nkind (A) = N_Real_Literal
2595 or else Nkind (A) = N_Integer_Literal
2596 or else Nkind (A) = N_Character_Literal
2597 then
2598 if Etype (F) /= Etype (A) then
2599 Set_Renamed_Object
2600 (F, Unchecked_Convert_To (Etype (F), Relocate_Node (A)));
2601 else
2602 Set_Renamed_Object (F, A);
2603 end if;
2605 else
2606 Temp :=
2607 Make_Defining_Identifier (Loc,
2608 Chars => New_Internal_Name ('C'));
2610 -- If the actual for an in/in-out parameter is a view conversion,
2611 -- make it into an unchecked conversion, given that an untagged
2612 -- type conversion is not a proper object for a renaming.
2614 -- In-out conversions that involve real conversions have already
2615 -- been transformed in Expand_Actuals.
2617 if Nkind (A) = N_Type_Conversion
2618 and then Ekind (F) /= E_In_Parameter
2619 then
2620 New_A := Make_Unchecked_Type_Conversion (Loc,
2621 Subtype_Mark => New_Occurrence_Of (Etype (F), Loc),
2622 Expression => Relocate_Node (Expression (A)));
2624 elsif Etype (F) /= Etype (A) then
2625 New_A := Unchecked_Convert_To (Etype (F), Relocate_Node (A));
2626 Temp_Typ := Etype (F);
2628 else
2629 New_A := Relocate_Node (A);
2630 end if;
2632 Set_Sloc (New_A, Sloc (N));
2634 if Ekind (F) = E_In_Parameter
2635 and then not Is_Limited_Type (Etype (A))
2636 then
2637 Decl :=
2638 Make_Object_Declaration (Loc,
2639 Defining_Identifier => Temp,
2640 Constant_Present => True,
2641 Object_Definition => New_Occurrence_Of (Temp_Typ, Loc),
2642 Expression => New_A);
2643 else
2644 Decl :=
2645 Make_Object_Renaming_Declaration (Loc,
2646 Defining_Identifier => Temp,
2647 Subtype_Mark => New_Occurrence_Of (Temp_Typ, Loc),
2648 Name => New_A);
2649 end if;
2651 Prepend (Decl, Declarations (Blk));
2652 Set_Renamed_Object (F, Temp);
2653 end if;
2655 Next_Formal (F);
2656 Next_Actual (A);
2657 end loop;
2659 -- Establish target of function call. If context is not assignment or
2660 -- declaration, create a temporary as a target. The declaration for
2661 -- the temporary may be subsequently optimized away if the body is a
2662 -- single expression, or if the left-hand side of the assignment is
2663 -- simple enough.
2665 if Ekind (Subp) = E_Function then
2666 if Nkind (Parent (N)) = N_Assignment_Statement
2667 and then Is_Entity_Name (Name (Parent (N)))
2668 then
2669 Targ := Name (Parent (N));
2671 else
2672 -- Replace call with temporary, and create its declaration.
2674 Temp :=
2675 Make_Defining_Identifier (Loc, New_Internal_Name ('C'));
2677 Decl :=
2678 Make_Object_Declaration (Loc,
2679 Defining_Identifier => Temp,
2680 Object_Definition =>
2681 New_Occurrence_Of (Ret_Type, Loc));
2683 Set_No_Initialization (Decl);
2684 Insert_Action (N, Decl);
2685 Rewrite (N, New_Occurrence_Of (Temp, Loc));
2686 Targ := Temp;
2687 end if;
2688 end if;
2690 -- Traverse the tree and replace formals with actuals or their thunks.
2691 -- Attach block to tree before analysis and rewriting.
2693 Replace_Formals (Blk);
2694 Set_Parent (Blk, N);
2696 if not Comes_From_Source (Subp)
2697 or else Is_Predef
2698 then
2699 Reset_Slocs (Blk);
2700 end if;
2702 if Present (Exit_Lab) then
2704 -- If the body was a single expression, the single return statement
2705 -- and the corresponding label are useless.
2707 if Num_Ret = 1
2708 and then
2709 Nkind (Last (Statements (Handled_Statement_Sequence (Blk)))) =
2710 N_Goto_Statement
2711 then
2712 Remove (Last (Statements (Handled_Statement_Sequence (Blk))));
2713 else
2714 Append (Lab_Decl, (Declarations (Blk)));
2715 Append (Exit_Lab, Statements (Handled_Statement_Sequence (Blk)));
2716 end if;
2717 end if;
2719 -- Analyze Blk with In_Inlined_Body set, to avoid spurious errors on
2720 -- conflicting private views that Gigi would ignore. If this is a
2721 -- predefined unit, analyze with checks off, as is done in the non-
2722 -- inlined run-time units.
2724 declare
2725 I_Flag : constant Boolean := In_Inlined_Body;
2727 begin
2728 In_Inlined_Body := True;
2730 if Is_Predef then
2731 declare
2732 Style : constant Boolean := Style_Check;
2733 begin
2734 Style_Check := False;
2735 Analyze (Blk, Suppress => All_Checks);
2736 Style_Check := Style;
2737 end;
2739 else
2740 Analyze (Blk);
2741 end if;
2743 In_Inlined_Body := I_Flag;
2744 end;
2746 if Ekind (Subp) = E_Procedure then
2747 Rewrite_Procedure_Call (N, Blk);
2748 else
2749 Rewrite_Function_Call (N, Blk);
2750 end if;
2752 Restore_Env;
2754 -- Cleanup mapping between formals and actuals, for other expansions.
2756 F := First_Formal (Subp);
2758 while Present (F) loop
2759 Set_Renamed_Object (F, Empty);
2760 Next_Formal (F);
2761 end loop;
2762 end Expand_Inlined_Call;
2764 ----------------------------
2765 -- Expand_N_Function_Call --
2766 ----------------------------
2768 procedure Expand_N_Function_Call (N : Node_Id) is
2769 Typ : constant Entity_Id := Etype (N);
2771 function Returned_By_Reference return Boolean;
2772 -- If the return type is returned through the secondary stack. that is
2773 -- by reference, we don't want to create a temp to force stack checking.
2775 function Returned_By_Reference return Boolean is
2776 S : Entity_Id := Current_Scope;
2778 begin
2779 if Is_Return_By_Reference_Type (Typ) then
2780 return True;
2782 elsif Nkind (Parent (N)) /= N_Return_Statement then
2783 return False;
2785 elsif Requires_Transient_Scope (Typ) then
2787 -- Verify that the return type of the enclosing function has
2788 -- the same constrained status as that of the expression.
2790 while Ekind (S) /= E_Function loop
2791 S := Scope (S);
2792 end loop;
2794 return Is_Constrained (Typ) = Is_Constrained (Etype (S));
2795 else
2796 return False;
2797 end if;
2798 end Returned_By_Reference;
2800 -- Start of processing for Expand_N_Function_Call
2802 begin
2803 -- A special check. If stack checking is enabled, and the return type
2804 -- might generate a large temporary, and the call is not the right
2805 -- side of an assignment, then generate an explicit temporary. We do
2806 -- this because otherwise gigi may generate a large temporary on the
2807 -- fly and this can cause trouble with stack checking.
2809 if May_Generate_Large_Temp (Typ)
2810 and then Nkind (Parent (N)) /= N_Assignment_Statement
2811 and then
2812 (Nkind (Parent (N)) /= N_Qualified_Expression
2813 or else Nkind (Parent (Parent (N))) /= N_Assignment_Statement)
2814 and then
2815 (Nkind (Parent (N)) /= N_Object_Declaration
2816 or else Expression (Parent (N)) /= N)
2817 and then not Returned_By_Reference
2818 then
2819 -- Note: it might be thought that it would be OK to use a call to
2820 -- Force_Evaluation here, but that's not good enough, because that
2821 -- results in a 'Reference construct that may still need a temporary.
2823 declare
2824 Loc : constant Source_Ptr := Sloc (N);
2825 Temp_Obj : constant Entity_Id :=
2826 Make_Defining_Identifier (Loc,
2827 Chars => New_Internal_Name ('F'));
2828 Temp_Typ : Entity_Id := Typ;
2829 Decl : Node_Id;
2830 A : Node_Id;
2831 F : Entity_Id;
2832 Proc : Entity_Id;
2834 begin
2835 if Is_Tagged_Type (Typ)
2836 and then Present (Controlling_Argument (N))
2837 then
2838 if Nkind (Parent (N)) /= N_Procedure_Call_Statement
2839 and then Nkind (Parent (N)) /= N_Function_Call
2840 then
2841 -- If this is a tag-indeterminate call, the object must
2842 -- be classwide.
2844 if Is_Tag_Indeterminate (N) then
2845 Temp_Typ := Class_Wide_Type (Typ);
2846 end if;
2848 else
2849 -- If this is a dispatching call that is itself the
2850 -- controlling argument of an enclosing call, the nominal
2851 -- subtype of the object that replaces it must be classwide,
2852 -- so that dispatching will take place properly. If it is
2853 -- not a controlling argument, the object is not classwide.
2855 Proc := Entity (Name (Parent (N)));
2856 F := First_Formal (Proc);
2857 A := First_Actual (Parent (N));
2859 while A /= N loop
2860 Next_Formal (F);
2861 Next_Actual (A);
2862 end loop;
2864 if Is_Controlling_Formal (F) then
2865 Temp_Typ := Class_Wide_Type (Typ);
2866 end if;
2867 end if;
2868 end if;
2870 Decl :=
2871 Make_Object_Declaration (Loc,
2872 Defining_Identifier => Temp_Obj,
2873 Object_Definition => New_Occurrence_Of (Temp_Typ, Loc),
2874 Constant_Present => True,
2875 Expression => Relocate_Node (N));
2876 Set_Assignment_OK (Decl);
2878 Insert_Actions (N, New_List (Decl));
2879 Rewrite (N, New_Occurrence_Of (Temp_Obj, Loc));
2880 end;
2882 -- Normal case, expand the call
2884 else
2885 Expand_Call (N);
2886 end if;
2887 end Expand_N_Function_Call;
2889 ---------------------------------------
2890 -- Expand_N_Procedure_Call_Statement --
2891 ---------------------------------------
2893 procedure Expand_N_Procedure_Call_Statement (N : Node_Id) is
2894 begin
2895 Expand_Call (N);
2896 end Expand_N_Procedure_Call_Statement;
2898 ------------------------------
2899 -- Expand_N_Subprogram_Body --
2900 ------------------------------
2902 -- Add poll call if ATC polling is enabled
2904 -- Add return statement if last statement in body is not a return
2905 -- statement (this makes things easier on Gigi which does not want
2906 -- to have to handle a missing return).
2908 -- Add call to Activate_Tasks if body is a task activator
2910 -- Deal with possible detection of infinite recursion
2912 -- Eliminate body completely if convention stubbed
2914 -- Encode entity names within body, since we will not need to reference
2915 -- these entities any longer in the front end.
2917 -- Initialize scalar out parameters if Initialize/Normalize_Scalars
2919 -- Reset Pure indication if any parameter has root type System.Address
2921 -- Wrap thread body
2923 procedure Expand_N_Subprogram_Body (N : Node_Id) is
2924 Loc : constant Source_Ptr := Sloc (N);
2925 H : constant Node_Id := Handled_Statement_Sequence (N);
2926 Body_Id : Entity_Id;
2927 Spec_Id : Entity_Id;
2928 Except_H : Node_Id;
2929 Scop : Entity_Id;
2930 Dec : Node_Id;
2931 Next_Op : Node_Id;
2932 L : List_Id;
2934 procedure Add_Return (S : List_Id);
2935 -- Append a return statement to the statement sequence S if the last
2936 -- statement is not already a return or a goto statement. Note that
2937 -- the latter test is not critical, it does not matter if we add a
2938 -- few extra returns, since they get eliminated anyway later on.
2940 procedure Expand_Thread_Body;
2941 -- Perform required expansion of a thread body
2943 ----------------
2944 -- Add_Return --
2945 ----------------
2947 procedure Add_Return (S : List_Id) is
2948 begin
2949 if not Is_Transfer (Last (S)) then
2951 -- The source location for the return is the end label
2952 -- of the procedure in all cases. This is a bit odd when
2953 -- there are exception handlers, but not much else we can do.
2955 Append_To (S, Make_Return_Statement (Sloc (End_Label (H))));
2956 end if;
2957 end Add_Return;
2959 ------------------------
2960 -- Expand_Thread_Body --
2961 ------------------------
2963 -- The required expansion of a thread body is as follows
2965 -- procedure <thread body procedure name> is
2967 -- _Secondary_Stack : aliased
2968 -- Storage_Elements.Storage_Array
2969 -- (1 .. Storage_Offset (Sec_Stack_Size));
2970 -- for _Secondary_Stack'Alignment use Standard'Maximum_Alignment;
2972 -- _Process_ATSD : aliased System.Threads.ATSD;
2974 -- begin
2975 -- System.Threads.Thread_Body_Enter;
2976 -- (_Secondary_Stack'Address,
2977 -- _Secondary_Stack'Length,
2978 -- _Process_ATSD'Address);
2980 -- declare
2981 -- <user declarations>
2982 -- begin
2983 -- <user statements>
2984 -- <user exception handlers>
2985 -- end;
2987 -- System.Threads.Thread_Body_Leave;
2989 -- exception
2990 -- when E : others =>
2991 -- System.Threads.Thread_Body_Exceptional_Exit (E);
2992 -- end;
2994 -- Note the exception handler is omitted if pragma Restriction
2995 -- No_Exception_Handlers is currently active.
2997 procedure Expand_Thread_Body is
2998 User_Decls : constant List_Id := Declarations (N);
2999 Sec_Stack_Len : Node_Id;
3001 TB_Pragma : constant Node_Id :=
3002 Get_Rep_Pragma (Spec_Id, Name_Thread_Body);
3004 Ent_SS : Entity_Id;
3005 Ent_ATSD : Entity_Id;
3006 Ent_EO : Entity_Id;
3008 Decl_SS : Node_Id;
3009 Decl_ATSD : Node_Id;
3011 Excep_Handlers : List_Id;
3013 begin
3014 New_Scope (Spec_Id);
3016 -- Get proper setting for secondary stack size
3018 if List_Length (Pragma_Argument_Associations (TB_Pragma)) = 2 then
3019 Sec_Stack_Len :=
3020 Expression (Last (Pragma_Argument_Associations (TB_Pragma)));
3021 else
3022 Sec_Stack_Len :=
3023 New_Occurrence_Of (RTE (RE_Default_Secondary_Stack_Size), Loc);
3024 end if;
3026 Sec_Stack_Len := Convert_To (RTE (RE_Storage_Offset), Sec_Stack_Len);
3028 -- Build and set declarations for the wrapped thread body
3030 Ent_SS := Make_Defining_Identifier (Loc, Name_uSecondary_Stack);
3031 Ent_ATSD := Make_Defining_Identifier (Loc, Name_uProcess_ATSD);
3033 Decl_SS :=
3034 Make_Object_Declaration (Loc,
3035 Defining_Identifier => Ent_SS,
3036 Aliased_Present => True,
3037 Object_Definition =>
3038 Make_Subtype_Indication (Loc,
3039 Subtype_Mark =>
3040 New_Occurrence_Of (RTE (RE_Storage_Array), Loc),
3041 Constraint =>
3042 Make_Index_Or_Discriminant_Constraint (Loc,
3043 Constraints => New_List (
3044 Make_Range (Loc,
3045 Low_Bound => Make_Integer_Literal (Loc, 1),
3046 High_Bound => Sec_Stack_Len)))));
3048 Decl_ATSD :=
3049 Make_Object_Declaration (Loc,
3050 Defining_Identifier => Ent_ATSD,
3051 Aliased_Present => True,
3052 Object_Definition => New_Occurrence_Of (RTE (RE_ATSD), Loc));
3054 Set_Declarations (N, New_List (Decl_SS, Decl_ATSD));
3055 Analyze (Decl_SS);
3056 Analyze (Decl_ATSD);
3057 Set_Alignment (Ent_SS, UI_From_Int (Maximum_Alignment));
3059 -- Create new exception handler
3061 if Restriction_Active (No_Exception_Handlers) then
3062 Excep_Handlers := No_List;
3064 else
3065 Check_Restriction (No_Exception_Handlers, N);
3067 Ent_EO := Make_Defining_Identifier (Loc, Name_uE);
3069 Excep_Handlers := New_List (
3070 Make_Exception_Handler (Loc,
3071 Choice_Parameter => Ent_EO,
3072 Exception_Choices => New_List (
3073 Make_Others_Choice (Loc)),
3074 Statements => New_List (
3075 Make_Procedure_Call_Statement (Loc,
3076 Name =>
3077 New_Occurrence_Of
3078 (RTE (RE_Thread_Body_Exceptional_Exit), Loc),
3079 Parameter_Associations => New_List (
3080 New_Occurrence_Of (Ent_EO, Loc))))));
3081 end if;
3083 -- Now build new handled statement sequence and analyze it
3085 Set_Handled_Statement_Sequence (N,
3086 Make_Handled_Sequence_Of_Statements (Loc,
3087 Statements => New_List (
3089 Make_Procedure_Call_Statement (Loc,
3090 Name => New_Occurrence_Of (RTE (RE_Thread_Body_Enter), Loc),
3091 Parameter_Associations => New_List (
3093 Make_Attribute_Reference (Loc,
3094 Prefix => New_Occurrence_Of (Ent_SS, Loc),
3095 Attribute_Name => Name_Address),
3097 Make_Attribute_Reference (Loc,
3098 Prefix => New_Occurrence_Of (Ent_SS, Loc),
3099 Attribute_Name => Name_Length),
3101 Make_Attribute_Reference (Loc,
3102 Prefix => New_Occurrence_Of (Ent_ATSD, Loc),
3103 Attribute_Name => Name_Address))),
3105 Make_Block_Statement (Loc,
3106 Declarations => User_Decls,
3107 Handled_Statement_Sequence => H),
3109 Make_Procedure_Call_Statement (Loc,
3110 Name => New_Occurrence_Of (RTE (RE_Thread_Body_Leave), Loc))),
3112 Exception_Handlers => Excep_Handlers));
3114 Analyze (Handled_Statement_Sequence (N));
3115 End_Scope;
3116 end Expand_Thread_Body;
3118 -- Start of processing for Expand_N_Subprogram_Body
3120 begin
3121 -- Set L to either the list of declarations if present, or
3122 -- to the list of statements if no declarations are present.
3123 -- This is used to insert new stuff at the start.
3125 if Is_Non_Empty_List (Declarations (N)) then
3126 L := Declarations (N);
3127 else
3128 L := Statements (Handled_Statement_Sequence (N));
3129 end if;
3131 -- Need poll on entry to subprogram if polling enabled. We only
3132 -- do this for non-empty subprograms, since it does not seem
3133 -- necessary to poll for a dummy null subprogram.
3135 if Is_Non_Empty_List (L) then
3136 Generate_Poll_Call (First (L));
3137 end if;
3139 -- Find entity for subprogram
3141 Body_Id := Defining_Entity (N);
3143 if Present (Corresponding_Spec (N)) then
3144 Spec_Id := Corresponding_Spec (N);
3145 else
3146 Spec_Id := Body_Id;
3147 end if;
3149 -- If this is a Pure function which has any parameters whose root
3150 -- type is System.Address, reset the Pure indication, since it will
3151 -- likely cause incorrect code to be generated as the parameter is
3152 -- probably a pointer, and the fact that the same pointer is passed
3153 -- does not mean that the same value is being referenced.
3155 -- Note that if the programmer gave an explicit Pure_Function pragma,
3156 -- then we believe the programmer, and leave the subprogram Pure.
3158 -- This code should probably be at the freeze point, so that it
3159 -- happens even on a -gnatc (or more importantly -gnatt) compile
3160 -- so that the semantic tree has Is_Pure set properly ???
3162 if Is_Pure (Spec_Id)
3163 and then Is_Subprogram (Spec_Id)
3164 and then not Has_Pragma_Pure_Function (Spec_Id)
3165 then
3166 declare
3167 F : Entity_Id := First_Formal (Spec_Id);
3169 begin
3170 while Present (F) loop
3171 if Is_RTE (Root_Type (Etype (F)), RE_Address) then
3172 Set_Is_Pure (Spec_Id, False);
3174 if Spec_Id /= Body_Id then
3175 Set_Is_Pure (Body_Id, False);
3176 end if;
3178 exit;
3179 end if;
3181 Next_Formal (F);
3182 end loop;
3183 end;
3184 end if;
3186 -- Initialize any scalar OUT args if Initialize/Normalize_Scalars
3188 if Init_Or_Norm_Scalars and then Is_Subprogram (Spec_Id) then
3189 declare
3190 F : Entity_Id := First_Formal (Spec_Id);
3191 V : constant Boolean := Validity_Checks_On;
3193 begin
3194 -- We turn off validity checking, since we do not want any
3195 -- check on the initializing value itself (which we know
3196 -- may well be invalid!)
3198 Validity_Checks_On := False;
3200 -- Loop through formals
3202 while Present (F) loop
3203 if Is_Scalar_Type (Etype (F))
3204 and then Ekind (F) = E_Out_Parameter
3205 then
3206 Insert_Before_And_Analyze (First (L),
3207 Make_Assignment_Statement (Loc,
3208 Name => New_Occurrence_Of (F, Loc),
3209 Expression => Get_Simple_Init_Val (Etype (F), Loc)));
3210 end if;
3212 Next_Formal (F);
3213 end loop;
3215 Validity_Checks_On := V;
3216 end;
3217 end if;
3219 Scop := Scope (Spec_Id);
3221 -- Add discriminal renamings to protected subprograms.
3222 -- Install new discriminals for expansion of the next
3223 -- subprogram of this protected type, if any.
3225 if Is_List_Member (N)
3226 and then Present (Parent (List_Containing (N)))
3227 and then Nkind (Parent (List_Containing (N))) = N_Protected_Body
3228 then
3229 Add_Discriminal_Declarations
3230 (Declarations (N), Scop, Name_uObject, Loc);
3231 Add_Private_Declarations (Declarations (N), Scop, Name_uObject, Loc);
3233 -- Associate privals and discriminals with the next protected
3234 -- operation body to be expanded. These are used to expand
3235 -- references to private data objects and discriminants,
3236 -- respectively.
3238 Next_Op := Next_Protected_Operation (N);
3240 if Present (Next_Op) then
3241 Dec := Parent (Base_Type (Scop));
3242 Set_Privals (Dec, Next_Op, Loc);
3243 Set_Discriminals (Dec);
3244 end if;
3245 end if;
3247 -- Clear out statement list for stubbed procedure
3249 if Present (Corresponding_Spec (N)) then
3250 Set_Elaboration_Flag (N, Spec_Id);
3252 if Convention (Spec_Id) = Convention_Stubbed
3253 or else Is_Eliminated (Spec_Id)
3254 then
3255 Set_Declarations (N, Empty_List);
3256 Set_Handled_Statement_Sequence (N,
3257 Make_Handled_Sequence_Of_Statements (Loc,
3258 Statements => New_List (
3259 Make_Null_Statement (Loc))));
3260 return;
3261 end if;
3262 end if;
3264 -- Returns_By_Ref flag is normally set when the subprogram is frozen
3265 -- but subprograms with no specs are not frozen
3267 declare
3268 Typ : constant Entity_Id := Etype (Spec_Id);
3269 Utyp : constant Entity_Id := Underlying_Type (Typ);
3271 begin
3272 if not Acts_As_Spec (N)
3273 and then Nkind (Parent (Parent (Spec_Id))) /=
3274 N_Subprogram_Body_Stub
3275 then
3276 null;
3278 elsif Is_Return_By_Reference_Type (Typ) then
3279 Set_Returns_By_Ref (Spec_Id);
3281 elsif Present (Utyp) and then Controlled_Type (Utyp) then
3282 Set_Returns_By_Ref (Spec_Id);
3283 end if;
3284 end;
3286 -- For a procedure, we add a return for all possible syntactic ends
3287 -- of the subprogram. Note that reanalysis is not necessary in this
3288 -- case since it would require a lot of work and accomplish nothing.
3290 if Ekind (Spec_Id) = E_Procedure
3291 or else Ekind (Spec_Id) = E_Generic_Procedure
3292 then
3293 Add_Return (Statements (H));
3295 if Present (Exception_Handlers (H)) then
3296 Except_H := First_Non_Pragma (Exception_Handlers (H));
3298 while Present (Except_H) loop
3299 Add_Return (Statements (Except_H));
3300 Next_Non_Pragma (Except_H);
3301 end loop;
3302 end if;
3304 -- For a function, we must deal with the case where there is at
3305 -- least one missing return. What we do is to wrap the entire body
3306 -- of the function in a block:
3308 -- begin
3309 -- ...
3310 -- end;
3312 -- becomes
3314 -- begin
3315 -- begin
3316 -- ...
3317 -- end;
3319 -- raise Program_Error;
3320 -- end;
3322 -- This approach is necessary because the raise must be signalled
3323 -- to the caller, not handled by any local handler (RM 6.4(11)).
3325 -- Note: we do not need to analyze the constructed sequence here,
3326 -- since it has no handler, and an attempt to analyze the handled
3327 -- statement sequence twice is risky in various ways (e.g. the
3328 -- issue of expanding cleanup actions twice).
3330 elsif Has_Missing_Return (Spec_Id) then
3331 declare
3332 Hloc : constant Source_Ptr := Sloc (H);
3333 Blok : constant Node_Id :=
3334 Make_Block_Statement (Hloc,
3335 Handled_Statement_Sequence => H);
3336 Rais : constant Node_Id :=
3337 Make_Raise_Program_Error (Hloc,
3338 Reason => PE_Missing_Return);
3340 begin
3341 Set_Handled_Statement_Sequence (N,
3342 Make_Handled_Sequence_Of_Statements (Hloc,
3343 Statements => New_List (Blok, Rais)));
3345 New_Scope (Spec_Id);
3346 Analyze (Blok);
3347 Analyze (Rais);
3348 Pop_Scope;
3349 end;
3350 end if;
3352 -- If subprogram contains a parameterless recursive call, then we may
3353 -- have an infinite recursion, so see if we can generate code to check
3354 -- for this possibility if storage checks are not suppressed.
3356 if Ekind (Spec_Id) = E_Procedure
3357 and then Has_Recursive_Call (Spec_Id)
3358 and then not Storage_Checks_Suppressed (Spec_Id)
3359 then
3360 Detect_Infinite_Recursion (N, Spec_Id);
3361 end if;
3363 -- Finally, if we are in Normalize_Scalars mode, then any scalar out
3364 -- parameters must be initialized to the appropriate default value.
3366 if Ekind (Spec_Id) = E_Procedure and then Normalize_Scalars then
3367 declare
3368 Floc : Source_Ptr;
3369 Formal : Entity_Id;
3370 Stm : Node_Id;
3372 begin
3373 Formal := First_Formal (Spec_Id);
3375 while Present (Formal) loop
3376 Floc := Sloc (Formal);
3378 if Ekind (Formal) = E_Out_Parameter
3379 and then Is_Scalar_Type (Etype (Formal))
3380 then
3381 Stm :=
3382 Make_Assignment_Statement (Floc,
3383 Name => New_Occurrence_Of (Formal, Floc),
3384 Expression =>
3385 Get_Simple_Init_Val (Etype (Formal), Floc));
3386 Prepend (Stm, Declarations (N));
3387 Analyze (Stm);
3388 end if;
3390 Next_Formal (Formal);
3391 end loop;
3392 end;
3393 end if;
3395 -- Deal with thread body
3397 if Is_Thread_Body (Spec_Id) then
3398 Expand_Thread_Body;
3399 end if;
3401 -- If the subprogram does not have pending instantiations, then we
3402 -- must generate the subprogram descriptor now, since the code for
3403 -- the subprogram is complete, and this is our last chance. However
3404 -- if there are pending instantiations, then the code is not
3405 -- complete, and we will delay the generation.
3407 if Is_Subprogram (Spec_Id)
3408 and then not Delay_Subprogram_Descriptors (Spec_Id)
3409 then
3410 Generate_Subprogram_Descriptor_For_Subprogram (N, Spec_Id);
3411 end if;
3413 -- Set to encode entity names in package body before gigi is called
3415 Qualify_Entity_Names (N);
3416 end Expand_N_Subprogram_Body;
3418 -----------------------------------
3419 -- Expand_N_Subprogram_Body_Stub --
3420 -----------------------------------
3422 procedure Expand_N_Subprogram_Body_Stub (N : Node_Id) is
3423 begin
3424 if Present (Corresponding_Body (N)) then
3425 Expand_N_Subprogram_Body (
3426 Unit_Declaration_Node (Corresponding_Body (N)));
3427 end if;
3428 end Expand_N_Subprogram_Body_Stub;
3430 -------------------------------------
3431 -- Expand_N_Subprogram_Declaration --
3432 -------------------------------------
3434 -- If the declaration appears within a protected body, it is a private
3435 -- operation of the protected type. We must create the corresponding
3436 -- protected subprogram an associated formals. For a normal protected
3437 -- operation, this is done when expanding the protected type declaration.
3439 procedure Expand_N_Subprogram_Declaration (N : Node_Id) is
3440 Loc : constant Source_Ptr := Sloc (N);
3441 Subp : constant Entity_Id := Defining_Entity (N);
3442 Scop : constant Entity_Id := Scope (Subp);
3443 Prot_Decl : Node_Id;
3444 Prot_Bod : Node_Id;
3445 Prot_Id : Entity_Id;
3447 begin
3448 -- Deal with case of protected subprogram. Do not generate
3449 -- protected operation if operation is flagged as eliminated.
3451 if Is_List_Member (N)
3452 and then Present (Parent (List_Containing (N)))
3453 and then Nkind (Parent (List_Containing (N))) = N_Protected_Body
3454 and then Is_Protected_Type (Scop)
3455 then
3456 if No (Protected_Body_Subprogram (Subp))
3457 and then not Is_Eliminated (Subp)
3458 then
3459 Prot_Decl :=
3460 Make_Subprogram_Declaration (Loc,
3461 Specification =>
3462 Build_Protected_Sub_Specification
3463 (N, Scop, Unprotected => True));
3465 -- The protected subprogram is declared outside of the protected
3466 -- body. Given that the body has frozen all entities so far, we
3467 -- analyze the subprogram and perform freezing actions explicitly.
3468 -- If the body is a subunit, the insertion point is before the
3469 -- stub in the parent.
3471 Prot_Bod := Parent (List_Containing (N));
3473 if Nkind (Parent (Prot_Bod)) = N_Subunit then
3474 Prot_Bod := Corresponding_Stub (Parent (Prot_Bod));
3475 end if;
3477 Insert_Before (Prot_Bod, Prot_Decl);
3478 Prot_Id := Defining_Unit_Name (Specification (Prot_Decl));
3480 New_Scope (Scope (Scop));
3481 Analyze (Prot_Decl);
3482 Create_Extra_Formals (Prot_Id);
3483 Set_Protected_Body_Subprogram (Subp, Prot_Id);
3484 Pop_Scope;
3485 end if;
3486 end if;
3487 end Expand_N_Subprogram_Declaration;
3489 ---------------------------------------
3490 -- Expand_Protected_Object_Reference --
3491 ---------------------------------------
3493 function Expand_Protected_Object_Reference
3494 (N : Node_Id;
3495 Scop : Entity_Id)
3496 return Node_Id
3498 Loc : constant Source_Ptr := Sloc (N);
3499 Corr : Entity_Id;
3500 Rec : Node_Id;
3501 Param : Entity_Id;
3502 Proc : Entity_Id;
3504 begin
3505 Rec := Make_Identifier (Loc, Name_uObject);
3506 Set_Etype (Rec, Corresponding_Record_Type (Scop));
3508 -- Find enclosing protected operation, and retrieve its first
3509 -- parameter, which denotes the enclosing protected object.
3510 -- If the enclosing operation is an entry, we are immediately
3511 -- within the protected body, and we can retrieve the object
3512 -- from the service entries procedure. A barrier function has
3513 -- has the same signature as an entry. A barrier function is
3514 -- compiled within the protected object, but unlike protected
3515 -- operations its never needs locks, so that its protected body
3516 -- subprogram points to itself.
3518 Proc := Current_Scope;
3520 while Present (Proc)
3521 and then Scope (Proc) /= Scop
3522 loop
3523 Proc := Scope (Proc);
3524 end loop;
3526 Corr := Protected_Body_Subprogram (Proc);
3528 if No (Corr) then
3530 -- Previous error left expansion incomplete.
3531 -- Nothing to do on this call.
3533 return Empty;
3534 end if;
3536 Param :=
3537 Defining_Identifier
3538 (First (Parameter_Specifications (Parent (Corr))));
3540 if Is_Subprogram (Proc)
3541 and then Proc /= Corr
3542 then
3543 -- Protected function or procedure.
3545 Set_Entity (Rec, Param);
3547 -- Rec is a reference to an entity which will not be in scope
3548 -- when the call is reanalyzed, and needs no further analysis.
3550 Set_Analyzed (Rec);
3552 else
3553 -- Entry or barrier function for entry body.
3554 -- The first parameter of the entry body procedure is a
3555 -- pointer to the object. We create a local variable
3556 -- of the proper type, duplicating what is done to define
3557 -- _object later on.
3559 declare
3560 Decls : List_Id;
3561 Obj_Ptr : constant Entity_Id := Make_Defining_Identifier (Loc,
3562 Chars =>
3563 New_Internal_Name ('T'));
3565 begin
3566 Decls := New_List (
3567 Make_Full_Type_Declaration (Loc,
3568 Defining_Identifier => Obj_Ptr,
3569 Type_Definition =>
3570 Make_Access_To_Object_Definition (Loc,
3571 Subtype_Indication =>
3572 New_Reference_To
3573 (Corresponding_Record_Type (Scop), Loc))));
3575 Insert_Actions (N, Decls);
3576 Insert_Actions (N, Freeze_Entity (Obj_Ptr, Sloc (N)));
3578 Rec :=
3579 Make_Explicit_Dereference (Loc,
3580 Unchecked_Convert_To (Obj_Ptr,
3581 New_Occurrence_Of (Param, Loc)));
3583 -- Analyze new actual. Other actuals in calls are already
3584 -- analyzed and the list of actuals is not renalyzed after
3585 -- rewriting.
3587 Set_Parent (Rec, N);
3588 Analyze (Rec);
3589 end;
3590 end if;
3592 return Rec;
3593 end Expand_Protected_Object_Reference;
3595 --------------------------------------
3596 -- Expand_Protected_Subprogram_Call --
3597 --------------------------------------
3599 procedure Expand_Protected_Subprogram_Call
3600 (N : Node_Id;
3601 Subp : Entity_Id;
3602 Scop : Entity_Id)
3604 Rec : Node_Id;
3606 begin
3607 -- If the protected object is not an enclosing scope, this is
3608 -- an inter-object function call. Inter-object procedure
3609 -- calls are expanded by Exp_Ch9.Build_Simple_Entry_Call.
3610 -- The call is intra-object only if the subprogram being
3611 -- called is in the protected body being compiled, and if the
3612 -- protected object in the call is statically the enclosing type.
3613 -- The object may be an component of some other data structure,
3614 -- in which case this must be handled as an inter-object call.
3616 if not In_Open_Scopes (Scop)
3617 or else not Is_Entity_Name (Name (N))
3618 then
3619 if Nkind (Name (N)) = N_Selected_Component then
3620 Rec := Prefix (Name (N));
3622 else
3623 pragma Assert (Nkind (Name (N)) = N_Indexed_Component);
3624 Rec := Prefix (Prefix (Name (N)));
3625 end if;
3627 Build_Protected_Subprogram_Call (N,
3628 Name => New_Occurrence_Of (Subp, Sloc (N)),
3629 Rec => Convert_Concurrent (Rec, Etype (Rec)),
3630 External => True);
3632 else
3633 Rec := Expand_Protected_Object_Reference (N, Scop);
3635 if No (Rec) then
3636 return;
3637 end if;
3639 Build_Protected_Subprogram_Call (N,
3640 Name => Name (N),
3641 Rec => Rec,
3642 External => False);
3644 end if;
3646 Analyze (N);
3648 -- If it is a function call it can appear in elaboration code and
3649 -- the called entity must be frozen here.
3651 if Ekind (Subp) = E_Function then
3652 Freeze_Expression (Name (N));
3653 end if;
3654 end Expand_Protected_Subprogram_Call;
3656 -----------------------
3657 -- Freeze_Subprogram --
3658 -----------------------
3660 procedure Freeze_Subprogram (N : Node_Id) is
3661 E : constant Entity_Id := Entity (N);
3663 begin
3664 -- When a primitive is frozen, enter its name in the corresponding
3665 -- dispatch table. If the DTC_Entity field is not set this is an
3666 -- overridden primitive that can be ignored. We suppress the
3667 -- initialization of the dispatch table entry when Java_VM because
3668 -- the dispatching mechanism is handled internally by the JVM.
3670 if Is_Dispatching_Operation (E)
3671 and then not Is_Abstract (E)
3672 and then Present (DTC_Entity (E))
3673 and then not Is_CPP_Class (Scope (DTC_Entity (E)))
3674 and then not Java_VM
3675 then
3676 Check_Overriding_Operation (E);
3677 Insert_After (N, Fill_DT_Entry (Sloc (N), E));
3678 end if;
3680 -- Mark functions that return by reference. Note that it cannot be
3681 -- part of the normal semantic analysis of the spec since the
3682 -- underlying returned type may not be known yet (for private types)
3684 declare
3685 Typ : constant Entity_Id := Etype (E);
3686 Utyp : constant Entity_Id := Underlying_Type (Typ);
3688 begin
3689 if Is_Return_By_Reference_Type (Typ) then
3690 Set_Returns_By_Ref (E);
3692 elsif Present (Utyp) and then Controlled_Type (Utyp) then
3693 Set_Returns_By_Ref (E);
3694 end if;
3695 end;
3696 end Freeze_Subprogram;
3698 end Exp_Ch6;