1 ------------------------------------------------------------------------------
3 -- GNAT COMPILER COMPONENTS --
9 -- Copyright (C) 1992-2006, Free Software Foundation, Inc. --
11 -- GNAT is free software; you can redistribute it and/or modify it under --
12 -- terms of the GNU General Public License as published by the Free Soft- --
13 -- ware Foundation; either version 2, or (at your option) any later ver- --
14 -- sion. GNAT is distributed in the hope that it will be useful, but WITH- --
15 -- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY --
16 -- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License --
17 -- for more details. You should have received a copy of the GNU General --
18 -- Public License distributed with GNAT; see file COPYING. If not, write --
19 -- to the Free Software Foundation, 51 Franklin Street, Fifth Floor, --
20 -- Boston, MA 02110-1301, USA. --
22 -- GNAT was originally developed by the GNAT team at New York University. --
23 -- Extensive contributions were provided by Ada Core Technologies Inc. --
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_Dbug
; use Exp_Dbug
;
38 with Exp_Disp
; use Exp_Disp
;
39 with Exp_Dist
; use Exp_Dist
;
40 with Exp_Intr
; use Exp_Intr
;
41 with Exp_Pakd
; use Exp_Pakd
;
42 with Exp_Tss
; use Exp_Tss
;
43 with Exp_Util
; use Exp_Util
;
44 with Fname
; use Fname
;
45 with Freeze
; use Freeze
;
46 with Hostparm
; use Hostparm
;
47 with Inline
; use Inline
;
49 with Nlists
; use Nlists
;
50 with Nmake
; use Nmake
;
52 with Restrict
; use Restrict
;
53 with Rident
; use Rident
;
54 with Rtsfind
; use Rtsfind
;
56 with Sem_Ch6
; use Sem_Ch6
;
57 with Sem_Ch8
; use Sem_Ch8
;
58 with Sem_Ch12
; use Sem_Ch12
;
59 with Sem_Ch13
; use Sem_Ch13
;
60 with Sem_Eval
; use Sem_Eval
;
61 with Sem_Disp
; use Sem_Disp
;
62 with Sem_Dist
; use Sem_Dist
;
63 with Sem_Mech
; use Sem_Mech
;
64 with Sem_Res
; use Sem_Res
;
65 with Sem_Type
; use Sem_Type
;
66 with Sem_Util
; use Sem_Util
;
67 with Sinfo
; use Sinfo
;
68 with Snames
; use Snames
;
69 with Stand
; use Stand
;
70 with Tbuild
; use Tbuild
;
71 with Ttypes
; use Ttypes
;
72 with Uintp
; use Uintp
;
73 with Validsw
; use Validsw
;
75 package body Exp_Ch6
is
77 -----------------------
78 -- Local Subprograms --
79 -----------------------
81 procedure Add_Access_Actual_To_Build_In_Place_Call
82 (Function_Call
: Node_Id
;
83 Function_Id
: Entity_Id
;
84 Return_Object
: Node_Id
);
85 -- Ada 2005 (AI-318-02): Apply the Unrestricted_Access attribute to the
86 -- object name given by Return_Object and add the attribute to the end of
87 -- the actual parameter list associated with the build-in-place function
88 -- call denoted by Function_Call.
90 procedure Check_Overriding_Operation
(Subp
: Entity_Id
);
91 -- Subp is a dispatching operation. Check whether it may override an
92 -- inherited private operation, in which case its DT entry is that of
93 -- the hidden operation, not the one it may have received earlier.
94 -- This must be done before emitting the code to set the corresponding
95 -- DT to the address of the subprogram. The actual placement of Subp in
96 -- the proper place in the list of primitive operations is done in
97 -- Declare_Inherited_Private_Subprograms, which also has to deal with
98 -- implicit operations. This duplication is unavoidable for now???
100 procedure Detect_Infinite_Recursion
(N
: Node_Id
; Spec
: Entity_Id
);
101 -- This procedure is called only if the subprogram body N, whose spec
102 -- has the given entity Spec, contains a parameterless recursive call.
103 -- It attempts to generate runtime code to detect if this a case of
104 -- infinite recursion.
106 -- The body is scanned to determine dependencies. If the only external
107 -- dependencies are on a small set of scalar variables, then the values
108 -- of these variables are captured on entry to the subprogram, and if
109 -- the values are not changed for the call, we know immediately that
110 -- we have an infinite recursion.
112 procedure Expand_Actuals
(N
: Node_Id
; Subp
: Entity_Id
);
113 -- For each actual of an in-out or out parameter which is a numeric
114 -- (view) conversion of the form T (A), where A denotes a variable,
115 -- we insert the declaration:
117 -- Temp : T[ := T (A)];
119 -- prior to the call. Then we replace the actual with a reference to Temp,
120 -- and append the assignment:
122 -- A := TypeA (Temp);
124 -- after the call. Here TypeA is the actual type of variable A.
125 -- For out parameters, the initial declaration has no expression.
126 -- If A is not an entity name, we generate instead:
128 -- Var : TypeA renames A;
129 -- Temp : T := Var; -- omitting expression for out parameter.
131 -- Var := TypeA (Temp);
133 -- For other in-out parameters, we emit the required constraint checks
134 -- before and/or after the call.
136 -- For all parameter modes, actuals that denote components and slices
137 -- of packed arrays are expanded into suitable temporaries.
139 -- For non-scalar objects that are possibly unaligned, add call by copy
140 -- code (copy in for IN and IN OUT, copy out for OUT and IN OUT).
142 procedure Expand_Inlined_Call
145 Orig_Subp
: Entity_Id
);
146 -- If called subprogram can be inlined by the front-end, retrieve the
147 -- analyzed body, replace formals with actuals and expand call in place.
148 -- Generate thunks for actuals that are expressions, and insert the
149 -- corresponding constant declarations before the call. If the original
150 -- call is to a derived operation, the return type is the one of the
151 -- derived operation, but the body is that of the original, so return
152 -- expressions in the body must be converted to the desired type (which
153 -- is simply not noted in the tree without inline expansion).
155 function Expand_Protected_Object_Reference
157 Scop
: Entity_Id
) return Node_Id
;
159 procedure Expand_Protected_Subprogram_Call
163 -- A call to a protected subprogram within the protected object may appear
164 -- as a regular call. The list of actuals must be expanded to contain a
165 -- reference to the object itself, and the call becomes a call to the
166 -- corresponding protected subprogram.
168 ----------------------------------------------
169 -- Add_Access_Actual_To_Build_In_Place_Call --
170 ----------------------------------------------
172 procedure Add_Access_Actual_To_Build_In_Place_Call
173 (Function_Call
: Node_Id
;
174 Function_Id
: Entity_Id
;
175 Return_Object
: Node_Id
)
177 Loc
: constant Source_Ptr
:= Sloc
(Function_Call
);
178 Obj_Address
: Node_Id
;
179 Obj_Acc_Formal
: Node_Id
;
180 Param_Assoc
: Node_Id
;
183 -- Locate the implicit access parameter in the called function. Maybe
184 -- we should be testing for the name of the access parameter (or perhaps
185 -- better, each implicit formal for build-in-place could have an
186 -- identifying flag, or a Uint attribute to identify it). ???
188 Obj_Acc_Formal
:= Extra_Formals
(Function_Id
);
190 while Present
(Obj_Acc_Formal
) loop
191 exit when Ekind
(Etype
(Obj_Acc_Formal
)) = E_Anonymous_Access_Type
;
192 Next_Formal_With_Extras
(Obj_Acc_Formal
);
195 pragma Assert
(Present
(Obj_Acc_Formal
));
197 -- Apply Unrestricted_Access to caller's return object
200 Make_Attribute_Reference
(Loc
,
201 Prefix
=> Return_Object
,
202 Attribute_Name
=> Name_Unrestricted_Access
);
204 Analyze_And_Resolve
(Obj_Address
, Etype
(Obj_Acc_Formal
));
206 -- Build the parameter association for the new actual and add it to the
207 -- end of the function's actuals.
210 Make_Parameter_Association
(Loc
,
211 Selector_Name
=> New_Occurrence_Of
(Obj_Acc_Formal
, Loc
),
212 Explicit_Actual_Parameter
=> Obj_Address
);
214 Set_Parent
(Param_Assoc
, Function_Call
);
215 Set_Parent
(Obj_Address
, Param_Assoc
);
217 if Present
(Parameter_Associations
(Function_Call
)) then
218 if Nkind
(Last
(Parameter_Associations
(Function_Call
))) =
219 N_Parameter_Association
221 Set_Next_Named_Actual
222 (Last
(Parameter_Associations
(Function_Call
)),
225 Set_First_Named_Actual
(Function_Call
, Obj_Address
);
228 Append
(Param_Assoc
, To
=> Parameter_Associations
(Function_Call
));
231 Set_Parameter_Associations
(Function_Call
, New_List
(Param_Assoc
));
232 Set_First_Named_Actual
(Function_Call
, Obj_Address
);
234 end Add_Access_Actual_To_Build_In_Place_Call
;
236 --------------------------------
237 -- Check_Overriding_Operation --
238 --------------------------------
240 procedure Check_Overriding_Operation
(Subp
: Entity_Id
) is
241 Typ
: constant Entity_Id
:= Find_Dispatching_Type
(Subp
);
242 Op_List
: constant Elist_Id
:= Primitive_Operations
(Typ
);
248 if Is_Derived_Type
(Typ
)
249 and then not Is_Private_Type
(Typ
)
250 and then In_Open_Scopes
(Scope
(Etype
(Typ
)))
251 and then Typ
= Base_Type
(Typ
)
253 -- Subp overrides an inherited private operation if there is an
254 -- inherited operation with a different name than Subp (see
255 -- Derive_Subprogram) whose Alias is a hidden subprogram with the
256 -- same name as Subp.
258 Op_Elmt
:= First_Elmt
(Op_List
);
259 while Present
(Op_Elmt
) loop
260 Prim_Op
:= Node
(Op_Elmt
);
261 Par_Op
:= Alias
(Prim_Op
);
264 and then not Comes_From_Source
(Prim_Op
)
265 and then Chars
(Prim_Op
) /= Chars
(Par_Op
)
266 and then Chars
(Par_Op
) = Chars
(Subp
)
267 and then Is_Hidden
(Par_Op
)
268 and then Type_Conformant
(Prim_Op
, Subp
)
270 Set_DT_Position
(Subp
, DT_Position
(Prim_Op
));
276 end Check_Overriding_Operation
;
278 -------------------------------
279 -- Detect_Infinite_Recursion --
280 -------------------------------
282 procedure Detect_Infinite_Recursion
(N
: Node_Id
; Spec
: Entity_Id
) is
283 Loc
: constant Source_Ptr
:= Sloc
(N
);
285 Var_List
: constant Elist_Id
:= New_Elmt_List
;
286 -- List of globals referenced by body of procedure
288 Call_List
: constant Elist_Id
:= New_Elmt_List
;
289 -- List of recursive calls in body of procedure
291 Shad_List
: constant Elist_Id
:= New_Elmt_List
;
292 -- List of entity id's for entities created to capture the value of
293 -- referenced globals on entry to the procedure.
295 Scop
: constant Uint
:= Scope_Depth
(Spec
);
296 -- This is used to record the scope depth of the current procedure, so
297 -- that we can identify global references.
299 Max_Vars
: constant := 4;
300 -- Do not test more than four global variables
302 Count_Vars
: Natural := 0;
303 -- Count variables found so far
315 function Process
(Nod
: Node_Id
) return Traverse_Result
;
316 -- Function to traverse the subprogram body (using Traverse_Func)
322 function Process
(Nod
: Node_Id
) return Traverse_Result
is
326 if Nkind
(Nod
) = N_Procedure_Call_Statement
then
328 -- Case of one of the detected recursive calls
330 if Is_Entity_Name
(Name
(Nod
))
331 and then Has_Recursive_Call
(Entity
(Name
(Nod
)))
332 and then Entity
(Name
(Nod
)) = Spec
334 Append_Elmt
(Nod
, Call_List
);
337 -- Any other procedure call may have side effects
343 -- A call to a pure function can always be ignored
345 elsif Nkind
(Nod
) = N_Function_Call
346 and then Is_Entity_Name
(Name
(Nod
))
347 and then Is_Pure
(Entity
(Name
(Nod
)))
351 -- Case of an identifier reference
353 elsif Nkind
(Nod
) = N_Identifier
then
356 -- If no entity, then ignore the reference
358 -- Not clear why this can happen. To investigate, remove this
359 -- test and look at the crash that occurs here in 3401-004 ???
364 -- Ignore entities with no Scope, again not clear how this
365 -- can happen, to investigate, look at 4108-008 ???
367 elsif No
(Scope
(Ent
)) then
370 -- Ignore the reference if not to a more global object
372 elsif Scope_Depth
(Scope
(Ent
)) >= Scop
then
375 -- References to types, exceptions and constants are always OK
378 or else Ekind
(Ent
) = E_Exception
379 or else Ekind
(Ent
) = E_Constant
383 -- If other than a non-volatile scalar variable, we have some
384 -- kind of global reference (e.g. to a function) that we cannot
385 -- deal with so we forget the attempt.
387 elsif Ekind
(Ent
) /= E_Variable
388 or else not Is_Scalar_Type
(Etype
(Ent
))
389 or else Treat_As_Volatile
(Ent
)
393 -- Otherwise we have a reference to a global scalar
396 -- Loop through global entities already detected
398 Elm
:= First_Elmt
(Var_List
);
400 -- If not detected before, record this new global reference
403 Count_Vars
:= Count_Vars
+ 1;
405 if Count_Vars
<= Max_Vars
then
406 Append_Elmt
(Entity
(Nod
), Var_List
);
413 -- If recorded before, ignore
415 elsif Node
(Elm
) = Entity
(Nod
) then
418 -- Otherwise keep looking
428 -- For all other node kinds, recursively visit syntactic children
435 function Traverse_Body
is new Traverse_Func
(Process
);
437 -- Start of processing for Detect_Infinite_Recursion
440 -- Do not attempt detection in No_Implicit_Conditional mode, since we
441 -- won't be able to generate the code to handle the recursion in any
444 if Restriction_Active
(No_Implicit_Conditionals
) then
448 -- Otherwise do traversal and quit if we get abandon signal
450 if Traverse_Body
(N
) = Abandon
then
453 -- We must have a call, since Has_Recursive_Call was set. If not just
454 -- ignore (this is only an error check, so if we have a funny situation,
455 -- due to bugs or errors, we do not want to bomb!)
457 elsif Is_Empty_Elmt_List
(Call_List
) then
461 -- Here is the case where we detect recursion at compile time
463 -- Push our current scope for analyzing the declarations and code that
464 -- we will insert for the checking.
468 -- This loop builds temporary variables for each of the referenced
469 -- globals, so that at the end of the loop the list Shad_List contains
470 -- these temporaries in one-to-one correspondence with the elements in
474 Elm
:= First_Elmt
(Var_List
);
475 while Present
(Elm
) loop
478 Make_Defining_Identifier
(Loc
,
479 Chars
=> New_Internal_Name
('S'));
480 Append_Elmt
(Ent
, Shad_List
);
482 -- Insert a declaration for this temporary at the start of the
483 -- declarations for the procedure. The temporaries are declared as
484 -- constant objects initialized to the current values of the
485 -- corresponding temporaries.
488 Make_Object_Declaration
(Loc
,
489 Defining_Identifier
=> Ent
,
490 Object_Definition
=> New_Occurrence_Of
(Etype
(Var
), Loc
),
491 Constant_Present
=> True,
492 Expression
=> New_Occurrence_Of
(Var
, Loc
));
495 Prepend
(Decl
, Declarations
(N
));
497 Insert_After
(Last
, Decl
);
505 -- Loop through calls
507 Call
:= First_Elmt
(Call_List
);
508 while Present
(Call
) loop
510 -- Build a predicate expression of the form
513 -- and then global1 = temp1
514 -- and then global2 = temp2
517 -- This predicate determines if any of the global values
518 -- referenced by the procedure have changed since the
519 -- current call, if not an infinite recursion is assured.
521 Test
:= New_Occurrence_Of
(Standard_True
, Loc
);
523 Elm1
:= First_Elmt
(Var_List
);
524 Elm2
:= First_Elmt
(Shad_List
);
525 while Present
(Elm1
) loop
531 Left_Opnd
=> New_Occurrence_Of
(Node
(Elm1
), Loc
),
532 Right_Opnd
=> New_Occurrence_Of
(Node
(Elm2
), Loc
)));
538 -- Now we replace the call with the sequence
540 -- if no-changes (see above) then
541 -- raise Storage_Error;
546 Rewrite
(Node
(Call
),
547 Make_If_Statement
(Loc
,
549 Then_Statements
=> New_List
(
550 Make_Raise_Storage_Error
(Loc
,
551 Reason
=> SE_Infinite_Recursion
)),
553 Else_Statements
=> New_List
(
554 Relocate_Node
(Node
(Call
)))));
556 Analyze
(Node
(Call
));
561 -- Remove temporary scope stack entry used for analysis
564 end Detect_Infinite_Recursion
;
570 procedure Expand_Actuals
(N
: Node_Id
; Subp
: Entity_Id
) is
571 Loc
: constant Source_Ptr
:= Sloc
(N
);
576 E_Formal
: Entity_Id
;
578 procedure Add_Call_By_Copy_Code
;
579 -- For cases where the parameter must be passed by copy, this routine
580 -- generates a temporary variable into which the actual is copied and
581 -- then passes this as the parameter. For an OUT or IN OUT parameter,
582 -- an assignment is also generated to copy the result back. The call
583 -- also takes care of any constraint checks required for the type
584 -- conversion case (on both the way in and the way out).
586 procedure Add_Simple_Call_By_Copy_Code
;
587 -- This is similar to the above, but is used in cases where we know
588 -- that all that is needed is to simply create a temporary and copy
589 -- the value in and out of the temporary.
591 procedure Check_Fortran_Logical
;
592 -- A value of type Logical that is passed through a formal parameter
593 -- must be normalized because .TRUE. usually does not have the same
594 -- representation as True. We assume that .FALSE. = False = 0.
595 -- What about functions that return a logical type ???
597 function Is_Legal_Copy
return Boolean;
598 -- Check that an actual can be copied before generating the temporary
599 -- to be used in the call. If the actual is of a by_reference type then
600 -- the program is illegal (this can only happen in the presence of
601 -- rep. clauses that force an incorrect alignment). If the formal is
602 -- a by_reference parameter imposed by a DEC pragma, emit a warning to
603 -- the effect that this might lead to unaligned arguments.
605 function Make_Var
(Actual
: Node_Id
) return Entity_Id
;
606 -- Returns an entity that refers to the given actual parameter,
607 -- Actual (not including any type conversion). If Actual is an
608 -- entity name, then this entity is returned unchanged, otherwise
609 -- a renaming is created to provide an entity for the actual.
611 procedure Reset_Packed_Prefix
;
612 -- The expansion of a packed array component reference is delayed in
613 -- the context of a call. Now we need to complete the expansion, so we
614 -- unmark the analyzed bits in all prefixes.
616 ---------------------------
617 -- Add_Call_By_Copy_Code --
618 ---------------------------
620 procedure Add_Call_By_Copy_Code
is
626 F_Typ
: constant Entity_Id
:= Etype
(Formal
);
631 if not Is_Legal_Copy
then
636 Make_Defining_Identifier
(Loc
,
637 Chars
=> New_Internal_Name
('T'));
639 -- Use formal type for temp, unless formal type is an unconstrained
640 -- array, in which case we don't have to worry about bounds checks,
641 -- and we use the actual type, since that has appropriate bounds.
643 if Is_Array_Type
(F_Typ
) and then not Is_Constrained
(F_Typ
) then
644 Indic
:= New_Occurrence_Of
(Etype
(Actual
), Loc
);
646 Indic
:= New_Occurrence_Of
(Etype
(Formal
), Loc
);
649 if Nkind
(Actual
) = N_Type_Conversion
then
650 V_Typ
:= Etype
(Expression
(Actual
));
652 -- If the formal is an (in-)out parameter, capture the name
653 -- of the variable in order to build the post-call assignment.
655 Var
:= Make_Var
(Expression
(Actual
));
657 Crep
:= not Same_Representation
658 (F_Typ
, Etype
(Expression
(Actual
)));
661 V_Typ
:= Etype
(Actual
);
662 Var
:= Make_Var
(Actual
);
666 -- Setup initialization for case of in out parameter, or an out
667 -- parameter where the formal is an unconstrained array (in the
668 -- latter case, we have to pass in an object with bounds).
670 -- If this is an out parameter, the initial copy is wasteful, so as
671 -- an optimization for the one-dimensional case we extract the
672 -- bounds of the actual and build an uninitialized temporary of the
675 if Ekind
(Formal
) = E_In_Out_Parameter
676 or else (Is_Array_Type
(F_Typ
) and then not Is_Constrained
(F_Typ
))
678 if Nkind
(Actual
) = N_Type_Conversion
then
679 if Conversion_OK
(Actual
) then
680 Init
:= OK_Convert_To
(F_Typ
, New_Occurrence_Of
(Var
, Loc
));
682 Init
:= Convert_To
(F_Typ
, New_Occurrence_Of
(Var
, Loc
));
685 elsif Ekind
(Formal
) = E_Out_Parameter
686 and then Is_Array_Type
(F_Typ
)
687 and then Number_Dimensions
(F_Typ
) = 1
688 and then not Has_Non_Null_Base_Init_Proc
(F_Typ
)
690 -- Actual is a one-dimensional array or slice, and the type
691 -- requires no initialization. Create a temporary of the
692 -- right size, but do not copy actual into it (optimization).
696 Make_Subtype_Indication
(Loc
,
698 New_Occurrence_Of
(F_Typ
, Loc
),
700 Make_Index_Or_Discriminant_Constraint
(Loc
,
701 Constraints
=> New_List
(
704 Make_Attribute_Reference
(Loc
,
705 Prefix
=> New_Occurrence_Of
(Var
, Loc
),
706 Attribute_name
=> Name_First
),
708 Make_Attribute_Reference
(Loc
,
709 Prefix
=> New_Occurrence_Of
(Var
, Loc
),
710 Attribute_Name
=> Name_Last
)))));
713 Init
:= New_Occurrence_Of
(Var
, Loc
);
716 -- An initialization is created for packed conversions as
717 -- actuals for out parameters to enable Make_Object_Declaration
718 -- to determine the proper subtype for N_Node. Note that this
719 -- is wasteful because the extra copying on the call side is
720 -- not required for such out parameters. ???
722 elsif Ekind
(Formal
) = E_Out_Parameter
723 and then Nkind
(Actual
) = N_Type_Conversion
724 and then (Is_Bit_Packed_Array
(F_Typ
)
726 Is_Bit_Packed_Array
(Etype
(Expression
(Actual
))))
728 if Conversion_OK
(Actual
) then
729 Init
:= OK_Convert_To
(F_Typ
, New_Occurrence_Of
(Var
, Loc
));
731 Init
:= Convert_To
(F_Typ
, New_Occurrence_Of
(Var
, Loc
));
734 elsif Ekind
(Formal
) = E_In_Parameter
then
736 -- Handle the case in which the actual is a type conversion
738 if Nkind
(Actual
) = N_Type_Conversion
then
739 if Conversion_OK
(Actual
) then
740 Init
:= OK_Convert_To
(F_Typ
, New_Occurrence_Of
(Var
, Loc
));
742 Init
:= Convert_To
(F_Typ
, New_Occurrence_Of
(Var
, Loc
));
745 Init
:= New_Occurrence_Of
(Var
, Loc
);
753 Make_Object_Declaration
(Loc
,
754 Defining_Identifier
=> Temp
,
755 Object_Definition
=> Indic
,
757 Set_Assignment_OK
(N_Node
);
758 Insert_Action
(N
, N_Node
);
760 -- Now, normally the deal here is that we use the defining
761 -- identifier created by that object declaration. There is
762 -- one exception to this. In the change of representation case
763 -- the above declaration will end up looking like:
765 -- temp : type := identifier;
767 -- And in this case we might as well use the identifier directly
768 -- and eliminate the temporary. Note that the analysis of the
769 -- declaration was not a waste of time in that case, since it is
770 -- what generated the necessary change of representation code. If
771 -- the change of representation introduced additional code, as in
772 -- a fixed-integer conversion, the expression is not an identifier
776 and then Present
(Expression
(N_Node
))
777 and then Is_Entity_Name
(Expression
(N_Node
))
779 Temp
:= Entity
(Expression
(N_Node
));
780 Rewrite
(N_Node
, Make_Null_Statement
(Loc
));
783 -- For IN parameter, all we do is to replace the actual
785 if Ekind
(Formal
) = E_In_Parameter
then
786 Rewrite
(Actual
, New_Reference_To
(Temp
, Loc
));
789 -- Processing for OUT or IN OUT parameter
792 -- Kill current value indications for the temporary variable we
793 -- created, since we just passed it as an OUT parameter.
795 Kill_Current_Values
(Temp
);
797 -- If type conversion, use reverse conversion on exit
799 if Nkind
(Actual
) = N_Type_Conversion
then
800 if Conversion_OK
(Actual
) then
801 Expr
:= OK_Convert_To
(V_Typ
, New_Occurrence_Of
(Temp
, Loc
));
803 Expr
:= Convert_To
(V_Typ
, New_Occurrence_Of
(Temp
, Loc
));
806 Expr
:= New_Occurrence_Of
(Temp
, Loc
);
809 Rewrite
(Actual
, New_Reference_To
(Temp
, Loc
));
812 Append_To
(Post_Call
,
813 Make_Assignment_Statement
(Loc
,
814 Name
=> New_Occurrence_Of
(Var
, Loc
),
815 Expression
=> Expr
));
817 Set_Assignment_OK
(Name
(Last
(Post_Call
)));
819 end Add_Call_By_Copy_Code
;
821 ----------------------------------
822 -- Add_Simple_Call_By_Copy_Code --
823 ----------------------------------
825 procedure Add_Simple_Call_By_Copy_Code
is
833 F_Typ
: constant Entity_Id
:= Etype
(Formal
);
836 if not Is_Legal_Copy
then
840 -- Use formal type for temp, unless formal type is an unconstrained
841 -- array, in which case we don't have to worry about bounds checks,
842 -- and we use the actual type, since that has appropriate bounds.
844 if Is_Array_Type
(F_Typ
) and then not Is_Constrained
(F_Typ
) then
845 Indic
:= New_Occurrence_Of
(Etype
(Actual
), Loc
);
847 Indic
:= New_Occurrence_Of
(Etype
(Formal
), Loc
);
850 -- Prepare to generate code
855 Make_Defining_Identifier
(Loc
,
856 Chars
=> New_Internal_Name
('T'));
857 Incod
:= Relocate_Node
(Actual
);
858 Outcod
:= New_Copy_Tree
(Incod
);
860 -- Generate declaration of temporary variable, initializing it
861 -- with the input parameter unless we have an OUT formal or
862 -- this is an initialization call.
864 -- If the formal is an out parameter with discriminants, the
865 -- discriminants must be captured even if the rest of the object
866 -- is in principle uninitialized, because the discriminants may
867 -- be read by the called subprogram.
869 if Ekind
(Formal
) = E_Out_Parameter
then
872 if Has_Discriminants
(Etype
(Formal
)) then
873 Indic
:= New_Occurrence_Of
(Etype
(Actual
), Loc
);
876 elsif Inside_Init_Proc
then
878 -- Could use a comment here to match comment below ???
880 if Nkind
(Actual
) /= N_Selected_Component
882 not Has_Discriminant_Dependent_Constraint
883 (Entity
(Selector_Name
(Actual
)))
887 -- Otherwise, keep the component in order to generate the proper
888 -- actual subtype, that depends on enclosing discriminants.
896 Make_Object_Declaration
(Loc
,
897 Defining_Identifier
=> Temp
,
898 Object_Definition
=> Indic
,
899 Expression
=> Incod
);
904 -- If the call is to initialize a component of a composite type,
905 -- and the component does not depend on discriminants, use the
906 -- actual type of the component. This is required in case the
907 -- component is constrained, because in general the formal of the
908 -- initialization procedure will be unconstrained. Note that if
909 -- the component being initialized is constrained by an enclosing
910 -- discriminant, the presence of the initialization in the
911 -- declaration will generate an expression for the actual subtype.
913 Set_No_Initialization
(Decl
);
914 Set_Object_Definition
(Decl
,
915 New_Occurrence_Of
(Etype
(Actual
), Loc
));
918 Insert_Action
(N
, Decl
);
920 -- The actual is simply a reference to the temporary
922 Rewrite
(Actual
, New_Occurrence_Of
(Temp
, Loc
));
924 -- Generate copy out if OUT or IN OUT parameter
926 if Ekind
(Formal
) /= E_In_Parameter
then
928 Rhs
:= New_Occurrence_Of
(Temp
, Loc
);
930 -- Deal with conversion
932 if Nkind
(Lhs
) = N_Type_Conversion
then
933 Lhs
:= Expression
(Lhs
);
934 Rhs
:= Convert_To
(Etype
(Actual
), Rhs
);
937 Append_To
(Post_Call
,
938 Make_Assignment_Statement
(Loc
,
941 Set_Assignment_OK
(Name
(Last
(Post_Call
)));
943 end Add_Simple_Call_By_Copy_Code
;
945 ---------------------------
946 -- Check_Fortran_Logical --
947 ---------------------------
949 procedure Check_Fortran_Logical
is
950 Logical
: constant Entity_Id
:= Etype
(Formal
);
953 -- Note: this is very incomplete, e.g. it does not handle arrays
954 -- of logical values. This is really not the right approach at all???)
957 if Convention
(Subp
) = Convention_Fortran
958 and then Root_Type
(Etype
(Formal
)) = Standard_Boolean
959 and then Ekind
(Formal
) /= E_In_Parameter
961 Var
:= Make_Var
(Actual
);
962 Append_To
(Post_Call
,
963 Make_Assignment_Statement
(Loc
,
964 Name
=> New_Occurrence_Of
(Var
, Loc
),
966 Unchecked_Convert_To
(
969 Left_Opnd
=> New_Occurrence_Of
(Var
, Loc
),
971 Unchecked_Convert_To
(
973 New_Occurrence_Of
(Standard_False
, Loc
))))));
975 end Check_Fortran_Logical
;
981 function Is_Legal_Copy
return Boolean is
983 -- An attempt to copy a value of such a type can only occur if
984 -- representation clauses give the actual a misaligned address.
986 if Is_By_Reference_Type
(Etype
(Formal
)) then
988 ("misaligned actual cannot be passed by reference", Actual
);
991 -- For users of Starlet, we assume that the specification of by-
992 -- reference mechanism is mandatory. This may lead to unligned
993 -- objects but at least for DEC legacy code it is known to work.
994 -- The warning will alert users of this code that a problem may
997 elsif Mechanism
(Formal
) = By_Reference
998 and then Is_Valued_Procedure
(Scope
(Formal
))
1001 ("by_reference actual may be misaligned?", Actual
);
1013 function Make_Var
(Actual
: Node_Id
) return Entity_Id
is
1017 if Is_Entity_Name
(Actual
) then
1018 return Entity
(Actual
);
1022 Make_Defining_Identifier
(Loc
,
1023 Chars
=> New_Internal_Name
('T'));
1026 Make_Object_Renaming_Declaration
(Loc
,
1027 Defining_Identifier
=> Var
,
1029 New_Occurrence_Of
(Etype
(Actual
), Loc
),
1030 Name
=> Relocate_Node
(Actual
));
1032 Insert_Action
(N
, N_Node
);
1037 -------------------------
1038 -- Reset_Packed_Prefix --
1039 -------------------------
1041 procedure Reset_Packed_Prefix
is
1042 Pfx
: Node_Id
:= Actual
;
1045 Set_Analyzed
(Pfx
, False);
1046 exit when Nkind
(Pfx
) /= N_Selected_Component
1047 and then Nkind
(Pfx
) /= N_Indexed_Component
;
1048 Pfx
:= Prefix
(Pfx
);
1050 end Reset_Packed_Prefix
;
1052 -- Start of processing for Expand_Actuals
1055 Post_Call
:= New_List
;
1057 Formal
:= First_Formal
(Subp
);
1058 Actual
:= First_Actual
(N
);
1059 while Present
(Formal
) loop
1060 E_Formal
:= Etype
(Formal
);
1062 if Is_Scalar_Type
(E_Formal
)
1063 or else Nkind
(Actual
) = N_Slice
1065 Check_Fortran_Logical
;
1069 elsif Ekind
(Formal
) /= E_Out_Parameter
then
1071 -- The unusual case of the current instance of a protected type
1072 -- requires special handling. This can only occur in the context
1073 -- of a call within the body of a protected operation.
1075 if Is_Entity_Name
(Actual
)
1076 and then Ekind
(Entity
(Actual
)) = E_Protected_Type
1077 and then In_Open_Scopes
(Entity
(Actual
))
1079 if Scope
(Subp
) /= Entity
(Actual
) then
1080 Error_Msg_N
("operation outside protected type may not "
1081 & "call back its protected operations?", Actual
);
1085 Expand_Protected_Object_Reference
(N
, Entity
(Actual
)));
1088 -- Ada 2005 (AI-318-02): If the actual parameter is a call to a
1089 -- build-in-place function, then a temporary return object needs
1090 -- to be created and access to it must be passed to the function.
1091 -- Currently we limit such functions to those with constrained
1092 -- inherently limited result subtypes, but eventually we plan to
1093 -- expand the allowed forms of funtions that are treated as
1096 if Ada_Version
>= Ada_05
1097 and then Is_Build_In_Place_Function_Call
(Actual
)
1099 Make_Build_In_Place_Call_In_Anonymous_Context
(Actual
);
1102 Apply_Constraint_Check
(Actual
, E_Formal
);
1104 -- Out parameter case. No constraint checks on access type
1107 elsif Is_Access_Type
(E_Formal
) then
1112 elsif Has_Discriminants
(Base_Type
(E_Formal
))
1113 or else Has_Non_Null_Base_Init_Proc
(E_Formal
)
1115 Apply_Constraint_Check
(Actual
, E_Formal
);
1120 Apply_Constraint_Check
(Actual
, Base_Type
(E_Formal
));
1123 -- Processing for IN-OUT and OUT parameters
1125 if Ekind
(Formal
) /= E_In_Parameter
then
1127 -- For type conversions of arrays, apply length/range checks
1129 if Is_Array_Type
(E_Formal
)
1130 and then Nkind
(Actual
) = N_Type_Conversion
1132 if Is_Constrained
(E_Formal
) then
1133 Apply_Length_Check
(Expression
(Actual
), E_Formal
);
1135 Apply_Range_Check
(Expression
(Actual
), E_Formal
);
1139 -- If argument is a type conversion for a type that is passed
1140 -- by copy, then we must pass the parameter by copy.
1142 if Nkind
(Actual
) = N_Type_Conversion
1144 (Is_Numeric_Type
(E_Formal
)
1145 or else Is_Access_Type
(E_Formal
)
1146 or else Is_Enumeration_Type
(E_Formal
)
1147 or else Is_Bit_Packed_Array
(Etype
(Formal
))
1148 or else Is_Bit_Packed_Array
(Etype
(Expression
(Actual
)))
1150 -- Also pass by copy if change of representation
1152 or else not Same_Representation
1154 Etype
(Expression
(Actual
))))
1156 Add_Call_By_Copy_Code
;
1158 -- References to components of bit packed arrays are expanded
1159 -- at this point, rather than at the point of analysis of the
1160 -- actuals, to handle the expansion of the assignment to
1161 -- [in] out parameters.
1163 elsif Is_Ref_To_Bit_Packed_Array
(Actual
) then
1164 Add_Simple_Call_By_Copy_Code
;
1166 -- If a non-scalar actual is possibly bit-aligned, we need a copy
1167 -- because the back-end cannot cope with such objects. In other
1168 -- cases where alignment forces a copy, the back-end generates
1169 -- it properly. It should not be generated unconditionally in the
1170 -- front-end because it does not know precisely the alignment
1171 -- requirements of the target, and makes too conservative an
1172 -- estimate, leading to superfluous copies or spurious errors
1173 -- on by-reference parameters.
1175 elsif Nkind
(Actual
) = N_Selected_Component
1177 Component_May_Be_Bit_Aligned
(Entity
(Selector_Name
(Actual
)))
1178 and then not Represented_As_Scalar
(Etype
(Formal
))
1180 Add_Simple_Call_By_Copy_Code
;
1182 -- References to slices of bit packed arrays are expanded
1184 elsif Is_Ref_To_Bit_Packed_Slice
(Actual
) then
1185 Add_Call_By_Copy_Code
;
1187 -- References to possibly unaligned slices of arrays are expanded
1189 elsif Is_Possibly_Unaligned_Slice
(Actual
) then
1190 Add_Call_By_Copy_Code
;
1192 -- Deal with access types where the actual subtpe and the
1193 -- formal subtype are not the same, requiring a check.
1195 -- It is necessary to exclude tagged types because of "downward
1196 -- conversion" errors and a strange assertion error in namet
1197 -- from gnatf in bug 1215-001 ???
1199 elsif Is_Access_Type
(E_Formal
)
1200 and then not Same_Type
(E_Formal
, Etype
(Actual
))
1201 and then not Is_Tagged_Type
(Designated_Type
(E_Formal
))
1203 Add_Call_By_Copy_Code
;
1205 -- If the actual is not a scalar and is marked for volatile
1206 -- treatment, whereas the formal is not volatile, then pass
1207 -- by copy unless it is a by-reference type.
1209 elsif Is_Entity_Name
(Actual
)
1210 and then Treat_As_Volatile
(Entity
(Actual
))
1211 and then not Is_By_Reference_Type
(Etype
(Actual
))
1212 and then not Is_Scalar_Type
(Etype
(Entity
(Actual
)))
1213 and then not Treat_As_Volatile
(E_Formal
)
1215 Add_Call_By_Copy_Code
;
1217 elsif Nkind
(Actual
) = N_Indexed_Component
1218 and then Is_Entity_Name
(Prefix
(Actual
))
1219 and then Has_Volatile_Components
(Entity
(Prefix
(Actual
)))
1221 Add_Call_By_Copy_Code
;
1224 -- Processing for IN parameters
1227 -- For IN parameters is in the packed array case, we expand an
1228 -- indexed component (the circuit in Exp_Ch4 deliberately left
1229 -- indexed components appearing as actuals untouched, so that
1230 -- the special processing above for the OUT and IN OUT cases
1231 -- could be performed. We could make the test in Exp_Ch4 more
1232 -- complex and have it detect the parameter mode, but it is
1233 -- easier simply to handle all cases here.)
1235 if Nkind
(Actual
) = N_Indexed_Component
1236 and then Is_Packed
(Etype
(Prefix
(Actual
)))
1238 Reset_Packed_Prefix
;
1239 Expand_Packed_Element_Reference
(Actual
);
1241 -- If we have a reference to a bit packed array, we copy it,
1242 -- since the actual must be byte aligned.
1244 -- Is this really necessary in all cases???
1246 elsif Is_Ref_To_Bit_Packed_Array
(Actual
) then
1247 Add_Simple_Call_By_Copy_Code
;
1249 -- If a non-scalar actual is possibly unaligned, we need a copy
1251 elsif Is_Possibly_Unaligned_Object
(Actual
)
1252 and then not Represented_As_Scalar
(Etype
(Formal
))
1254 Add_Simple_Call_By_Copy_Code
;
1256 -- Similarly, we have to expand slices of packed arrays here
1257 -- because the result must be byte aligned.
1259 elsif Is_Ref_To_Bit_Packed_Slice
(Actual
) then
1260 Add_Call_By_Copy_Code
;
1262 -- Only processing remaining is to pass by copy if this is a
1263 -- reference to a possibly unaligned slice, since the caller
1264 -- expects an appropriately aligned argument.
1266 elsif Is_Possibly_Unaligned_Slice
(Actual
) then
1267 Add_Call_By_Copy_Code
;
1271 Next_Formal
(Formal
);
1272 Next_Actual
(Actual
);
1275 -- Find right place to put post call stuff if it is present
1277 if not Is_Empty_List
(Post_Call
) then
1279 -- If call is not a list member, it must be the triggering statement
1280 -- of a triggering alternative or an entry call alternative, and we
1281 -- can add the post call stuff to the corresponding statement list.
1283 if not Is_List_Member
(N
) then
1285 P
: constant Node_Id
:= Parent
(N
);
1288 pragma Assert
(Nkind
(P
) = N_Triggering_Alternative
1289 or else Nkind
(P
) = N_Entry_Call_Alternative
);
1291 if Is_Non_Empty_List
(Statements
(P
)) then
1292 Insert_List_Before_And_Analyze
1293 (First
(Statements
(P
)), Post_Call
);
1295 Set_Statements
(P
, Post_Call
);
1299 -- Otherwise, normal case where N is in a statement sequence,
1300 -- just put the post-call stuff after the call statement.
1303 Insert_Actions_After
(N
, Post_Call
);
1307 -- The call node itself is re-analyzed in Expand_Call
1315 -- This procedure handles expansion of function calls and procedure call
1316 -- statements (i.e. it serves as the body for Expand_N_Function_Call and
1317 -- Expand_N_Procedure_Call_Statement. Processing for calls includes:
1319 -- Replace call to Raise_Exception by Raise_Exception always if possible
1320 -- Provide values of actuals for all formals in Extra_Formals list
1321 -- Replace "call" to enumeration literal function by literal itself
1322 -- Rewrite call to predefined operator as operator
1323 -- Replace actuals to in-out parameters that are numeric conversions,
1324 -- with explicit assignment to temporaries before and after the call.
1325 -- Remove optional actuals if First_Optional_Parameter specified.
1327 -- Note that the list of actuals has been filled with default expressions
1328 -- during semantic analysis of the call. Only the extra actuals required
1329 -- for the 'Constrained attribute and for accessibility checks are added
1332 procedure Expand_Call
(N
: Node_Id
) is
1333 Loc
: constant Source_Ptr
:= Sloc
(N
);
1334 Remote
: constant Boolean := Is_Remote_Call
(N
);
1336 Orig_Subp
: Entity_Id
:= Empty
;
1337 Parent_Subp
: Entity_Id
;
1338 Parent_Formal
: Entity_Id
;
1341 Prev
: Node_Id
:= Empty
;
1343 Prev_Orig
: Node_Id
;
1344 -- Original node for an actual, which may have been rewritten. If the
1345 -- actual is a function call that has been transformed from a selected
1346 -- component, the original node is unanalyzed. Otherwise, it carries
1347 -- semantic information used to generate additional actuals.
1350 Extra_Actuals
: List_Id
:= No_List
;
1352 CW_Interface_Formals_Present
: Boolean := False;
1354 procedure Add_Actual_Parameter
(Insert_Param
: Node_Id
);
1355 -- Adds one entry to the end of the actual parameter list. Used for
1356 -- default parameters and for extra actuals (for Extra_Formals). The
1357 -- argument is an N_Parameter_Association node.
1359 procedure Add_Extra_Actual
(Expr
: Node_Id
; EF
: Entity_Id
);
1360 -- Adds an extra actual to the list of extra actuals. Expr is the
1361 -- expression for the value of the actual, EF is the entity for the
1364 function Inherited_From_Formal
(S
: Entity_Id
) return Entity_Id
;
1365 -- Within an instance, a type derived from a non-tagged formal derived
1366 -- type inherits from the original parent, not from the actual. This is
1367 -- tested in 4723-003. The current derivation mechanism has the derived
1368 -- type inherit from the actual, which is only correct outside of the
1369 -- instance. If the subprogram is inherited, we test for this particular
1370 -- case through a convoluted tree traversal before setting the proper
1371 -- subprogram to be called.
1373 --------------------------
1374 -- Add_Actual_Parameter --
1375 --------------------------
1377 procedure Add_Actual_Parameter
(Insert_Param
: Node_Id
) is
1378 Actual_Expr
: constant Node_Id
:=
1379 Explicit_Actual_Parameter
(Insert_Param
);
1382 -- Case of insertion is first named actual
1384 if No
(Prev
) or else
1385 Nkind
(Parent
(Prev
)) /= N_Parameter_Association
1387 Set_Next_Named_Actual
(Insert_Param
, First_Named_Actual
(N
));
1388 Set_First_Named_Actual
(N
, Actual_Expr
);
1391 if No
(Parameter_Associations
(N
)) then
1392 Set_Parameter_Associations
(N
, New_List
);
1393 Append
(Insert_Param
, Parameter_Associations
(N
));
1396 Insert_After
(Prev
, Insert_Param
);
1399 -- Case of insertion is not first named actual
1402 Set_Next_Named_Actual
1403 (Insert_Param
, Next_Named_Actual
(Parent
(Prev
)));
1404 Set_Next_Named_Actual
(Parent
(Prev
), Actual_Expr
);
1405 Append
(Insert_Param
, Parameter_Associations
(N
));
1408 Prev
:= Actual_Expr
;
1409 end Add_Actual_Parameter
;
1411 ----------------------
1412 -- Add_Extra_Actual --
1413 ----------------------
1415 procedure Add_Extra_Actual
(Expr
: Node_Id
; EF
: Entity_Id
) is
1416 Loc
: constant Source_Ptr
:= Sloc
(Expr
);
1419 if Extra_Actuals
= No_List
then
1420 Extra_Actuals
:= New_List
;
1421 Set_Parent
(Extra_Actuals
, N
);
1424 Append_To
(Extra_Actuals
,
1425 Make_Parameter_Association
(Loc
,
1426 Explicit_Actual_Parameter
=> Expr
,
1428 Make_Identifier
(Loc
, Chars
(EF
))));
1430 Analyze_And_Resolve
(Expr
, Etype
(EF
));
1431 end Add_Extra_Actual
;
1433 ---------------------------
1434 -- Inherited_From_Formal --
1435 ---------------------------
1437 function Inherited_From_Formal
(S
: Entity_Id
) return Entity_Id
is
1439 Gen_Par
: Entity_Id
;
1440 Gen_Prim
: Elist_Id
;
1445 -- If the operation is inherited, it is attached to the corresponding
1446 -- type derivation. If the parent in the derivation is a generic
1447 -- actual, it is a subtype of the actual, and we have to recover the
1448 -- original derived type declaration to find the proper parent.
1450 if Nkind
(Parent
(S
)) /= N_Full_Type_Declaration
1451 or else not Is_Derived_Type
(Defining_Identifier
(Parent
(S
)))
1452 or else Nkind
(Type_Definition
(Original_Node
(Parent
(S
)))) /=
1453 N_Derived_Type_Definition
1454 or else not In_Instance
1461 (Type_Definition
(Original_Node
(Parent
(S
)))));
1463 if Nkind
(Indic
) = N_Subtype_Indication
then
1464 Par
:= Entity
(Subtype_Mark
(Indic
));
1466 Par
:= Entity
(Indic
);
1470 if not Is_Generic_Actual_Type
(Par
)
1471 or else Is_Tagged_Type
(Par
)
1472 or else Nkind
(Parent
(Par
)) /= N_Subtype_Declaration
1473 or else not In_Open_Scopes
(Scope
(Par
))
1478 Gen_Par
:= Generic_Parent_Type
(Parent
(Par
));
1481 -- If the generic parent type is still the generic type, this is a
1482 -- private formal, not a derived formal, and there are no operations
1483 -- inherited from the formal.
1485 if Nkind
(Parent
(Gen_Par
)) = N_Formal_Type_Declaration
then
1489 Gen_Prim
:= Collect_Primitive_Operations
(Gen_Par
);
1491 Elmt
:= First_Elmt
(Gen_Prim
);
1492 while Present
(Elmt
) loop
1493 if Chars
(Node
(Elmt
)) = Chars
(S
) then
1499 F1
:= First_Formal
(S
);
1500 F2
:= First_Formal
(Node
(Elmt
));
1502 and then Present
(F2
)
1504 if Etype
(F1
) = Etype
(F2
)
1505 or else Etype
(F2
) = Gen_Par
1511 exit; -- not the right subprogram
1523 raise Program_Error
;
1524 end Inherited_From_Formal
;
1526 -- Start of processing for Expand_Call
1529 -- Ignore if previous error
1531 if Nkind
(N
) in N_Has_Etype
and then Etype
(N
) = Any_Type
then
1535 -- Call using access to subprogram with explicit dereference
1537 if Nkind
(Name
(N
)) = N_Explicit_Dereference
then
1538 Subp
:= Etype
(Name
(N
));
1539 Parent_Subp
:= Empty
;
1541 -- Case of call to simple entry, where the Name is a selected component
1542 -- whose prefix is the task, and whose selector name is the entry name
1544 elsif Nkind
(Name
(N
)) = N_Selected_Component
then
1545 Subp
:= Entity
(Selector_Name
(Name
(N
)));
1546 Parent_Subp
:= Empty
;
1548 -- Case of call to member of entry family, where Name is an indexed
1549 -- component, with the prefix being a selected component giving the
1550 -- task and entry family name, and the index being the entry index.
1552 elsif Nkind
(Name
(N
)) = N_Indexed_Component
then
1553 Subp
:= Entity
(Selector_Name
(Prefix
(Name
(N
))));
1554 Parent_Subp
:= Empty
;
1559 Subp
:= Entity
(Name
(N
));
1560 Parent_Subp
:= Alias
(Subp
);
1562 -- Replace call to Raise_Exception by call to Raise_Exception_Always
1563 -- if we can tell that the first parameter cannot possibly be null.
1564 -- This helps optimization and also generation of warnings.
1566 if not Restriction_Active
(No_Exception_Handlers
)
1567 and then Is_RTE
(Subp
, RE_Raise_Exception
)
1570 FA
: constant Node_Id
:= Original_Node
(First_Actual
(N
));
1573 -- The case we catch is where the first argument is obtained
1574 -- using the Identity attribute (which must always be
1577 if Nkind
(FA
) = N_Attribute_Reference
1578 and then Attribute_Name
(FA
) = Name_Identity
1580 Subp
:= RTE
(RE_Raise_Exception_Always
);
1581 Set_Entity
(Name
(N
), Subp
);
1586 if Ekind
(Subp
) = E_Entry
then
1587 Parent_Subp
:= Empty
;
1591 -- Ada 2005 (AI-345): We have a procedure call as a triggering
1592 -- alternative in an asynchronous select or as an entry call in
1593 -- a conditional or timed select. Check whether the procedure call
1594 -- is a renaming of an entry and rewrite it as an entry call.
1596 if Ada_Version
>= Ada_05
1597 and then Nkind
(N
) = N_Procedure_Call_Statement
1599 ((Nkind
(Parent
(N
)) = N_Triggering_Alternative
1600 and then Triggering_Statement
(Parent
(N
)) = N
)
1602 (Nkind
(Parent
(N
)) = N_Entry_Call_Alternative
1603 and then Entry_Call_Statement
(Parent
(N
)) = N
))
1607 Ren_Root
: Entity_Id
:= Subp
;
1610 -- This may be a chain of renamings, find the root
1612 if Present
(Alias
(Ren_Root
)) then
1613 Ren_Root
:= Alias
(Ren_Root
);
1616 if Present
(Original_Node
(Parent
(Parent
(Ren_Root
)))) then
1617 Ren_Decl
:= Original_Node
(Parent
(Parent
(Ren_Root
)));
1619 if Nkind
(Ren_Decl
) = N_Subprogram_Renaming_Declaration
then
1621 Make_Entry_Call_Statement
(Loc
,
1623 New_Copy_Tree
(Name
(Ren_Decl
)),
1624 Parameter_Associations
=>
1625 New_Copy_List_Tree
(Parameter_Associations
(N
))));
1633 -- First step, compute extra actuals, corresponding to any
1634 -- Extra_Formals present. Note that we do not access Extra_Formals
1635 -- directly, instead we simply note the presence of the extra
1636 -- formals as we process the regular formals and collect the
1637 -- corresponding actuals in Extra_Actuals.
1639 -- We also generate any required range checks for actuals as we go
1640 -- through the loop, since this is a convenient place to do this.
1642 Formal
:= First_Formal
(Subp
);
1643 Actual
:= First_Actual
(N
);
1644 while Present
(Formal
) loop
1646 -- Generate range check if required (not activated yet ???)
1648 -- if Do_Range_Check (Actual) then
1649 -- Set_Do_Range_Check (Actual, False);
1650 -- Generate_Range_Check
1651 -- (Actual, Etype (Formal), CE_Range_Check_Failed);
1654 -- Prepare to examine current entry
1657 Prev_Orig
:= Original_Node
(Prev
);
1659 if not Analyzed
(Prev_Orig
)
1660 and then Nkind
(Actual
) = N_Function_Call
1665 -- Ada 2005 (AI-251): Check if any formal is a class-wide interface
1666 -- to expand it in a further round.
1668 CW_Interface_Formals_Present
:=
1669 CW_Interface_Formals_Present
1671 (Ekind
(Etype
(Formal
)) = E_Class_Wide_Type
1672 and then Is_Interface
(Etype
(Etype
(Formal
))))
1674 (Ekind
(Etype
(Formal
)) = E_Anonymous_Access_Type
1675 and then Is_Interface
(Directly_Designated_Type
1676 (Etype
(Etype
(Formal
)))));
1678 -- Create possible extra actual for constrained case. Usually, the
1679 -- extra actual is of the form actual'constrained, but since this
1680 -- attribute is only available for unconstrained records, TRUE is
1681 -- expanded if the type of the formal happens to be constrained (for
1682 -- instance when this procedure is inherited from an unconstrained
1683 -- record to a constrained one) or if the actual has no discriminant
1684 -- (its type is constrained). An exception to this is the case of a
1685 -- private type without discriminants. In this case we pass FALSE
1686 -- because the object has underlying discriminants with defaults.
1688 if Present
(Extra_Constrained
(Formal
)) then
1689 if Ekind
(Etype
(Prev
)) in Private_Kind
1690 and then not Has_Discriminants
(Base_Type
(Etype
(Prev
)))
1693 New_Occurrence_Of
(Standard_False
, Loc
),
1694 Extra_Constrained
(Formal
));
1696 elsif Is_Constrained
(Etype
(Formal
))
1697 or else not Has_Discriminants
(Etype
(Prev
))
1700 New_Occurrence_Of
(Standard_True
, Loc
),
1701 Extra_Constrained
(Formal
));
1703 -- Do not produce extra actuals for Unchecked_Union parameters.
1704 -- Jump directly to the end of the loop.
1706 elsif Is_Unchecked_Union
(Base_Type
(Etype
(Actual
))) then
1707 goto Skip_Extra_Actual_Generation
;
1710 -- If the actual is a type conversion, then the constrained
1711 -- test applies to the actual, not the target type.
1717 -- Test for unchecked conversions as well, which can occur
1718 -- as out parameter actuals on calls to stream procedures.
1721 while Nkind
(Act_Prev
) = N_Type_Conversion
1722 or else Nkind
(Act_Prev
) = N_Unchecked_Type_Conversion
1724 Act_Prev
:= Expression
(Act_Prev
);
1727 -- If the expression is a conversion of a dereference,
1728 -- this is internally generated code that manipulates
1729 -- addresses, e.g. when building interface tables. No
1730 -- check should occur in this case, and the discriminated
1731 -- object is not directly a hand.
1733 if not Comes_From_Source
(Actual
)
1734 and then Nkind
(Actual
) = N_Unchecked_Type_Conversion
1735 and then Nkind
(Act_Prev
) = N_Explicit_Dereference
1738 (New_Occurrence_Of
(Standard_False
, Loc
),
1739 Extra_Constrained
(Formal
));
1743 (Make_Attribute_Reference
(Sloc
(Prev
),
1745 Duplicate_Subexpr_No_Checks
1746 (Act_Prev
, Name_Req
=> True),
1747 Attribute_Name
=> Name_Constrained
),
1748 Extra_Constrained
(Formal
));
1754 -- Create possible extra actual for accessibility level
1756 if Present
(Extra_Accessibility
(Formal
)) then
1757 if Is_Entity_Name
(Prev_Orig
) then
1759 -- When passing an access parameter as the actual to another
1760 -- access parameter we need to pass along the actual's own
1761 -- associated access level parameter. This is done if we are
1762 -- in the scope of the formal access parameter (if this is an
1763 -- inlined body the extra formal is irrelevant).
1765 if Ekind
(Entity
(Prev_Orig
)) in Formal_Kind
1766 and then Ekind
(Etype
(Prev_Orig
)) = E_Anonymous_Access_Type
1767 and then In_Open_Scopes
(Scope
(Entity
(Prev_Orig
)))
1770 Parm_Ent
: constant Entity_Id
:= Param_Entity
(Prev_Orig
);
1773 pragma Assert
(Present
(Parm_Ent
));
1775 if Present
(Extra_Accessibility
(Parm_Ent
)) then
1778 (Extra_Accessibility
(Parm_Ent
), Loc
),
1779 Extra_Accessibility
(Formal
));
1781 -- If the actual access parameter does not have an
1782 -- associated extra formal providing its scope level,
1783 -- then treat the actual as having library-level
1788 (Make_Integer_Literal
(Loc
,
1789 Intval
=> Scope_Depth
(Standard_Standard
)),
1790 Extra_Accessibility
(Formal
));
1794 -- The actual is a normal access value, so just pass the
1795 -- level of the actual's access type.
1799 (Make_Integer_Literal
(Loc
,
1800 Intval
=> Type_Access_Level
(Etype
(Prev_Orig
))),
1801 Extra_Accessibility
(Formal
));
1805 case Nkind
(Prev_Orig
) is
1807 when N_Attribute_Reference
=>
1809 case Get_Attribute_Id
(Attribute_Name
(Prev_Orig
)) is
1811 -- For X'Access, pass on the level of the prefix X
1813 when Attribute_Access
=>
1815 Make_Integer_Literal
(Loc
,
1817 Object_Access_Level
(Prefix
(Prev_Orig
))),
1818 Extra_Accessibility
(Formal
));
1820 -- Treat the unchecked attributes as library-level
1822 when Attribute_Unchecked_Access |
1823 Attribute_Unrestricted_Access
=>
1825 Make_Integer_Literal
(Loc
,
1826 Intval
=> Scope_Depth
(Standard_Standard
)),
1827 Extra_Accessibility
(Formal
));
1829 -- No other cases of attributes returning access
1830 -- values that can be passed to access parameters
1833 raise Program_Error
;
1837 -- For allocators we pass the level of the execution of
1838 -- the called subprogram, which is one greater than the
1839 -- current scope level.
1843 Make_Integer_Literal
(Loc
,
1844 Scope_Depth
(Current_Scope
) + 1),
1845 Extra_Accessibility
(Formal
));
1847 -- For other cases we simply pass the level of the
1848 -- actual's access type.
1852 Make_Integer_Literal
(Loc
,
1853 Intval
=> Type_Access_Level
(Etype
(Prev_Orig
))),
1854 Extra_Accessibility
(Formal
));
1860 -- Perform the check of 4.6(49) that prevents a null value from being
1861 -- passed as an actual to an access parameter. Note that the check is
1862 -- elided in the common cases of passing an access attribute or
1863 -- access parameter as an actual. Also, we currently don't enforce
1864 -- this check for expander-generated actuals and when -gnatdj is set.
1866 if Ada_Version
>= Ada_05
then
1868 -- Ada 2005 (AI-231): Check null-excluding access types
1870 if Is_Access_Type
(Etype
(Formal
))
1871 and then Can_Never_Be_Null
(Etype
(Formal
))
1872 and then Nkind
(Prev
) /= N_Raise_Constraint_Error
1873 and then (Nkind
(Prev
) = N_Null
1874 or else not Can_Never_Be_Null
(Etype
(Prev
)))
1876 Install_Null_Excluding_Check
(Prev
);
1879 -- Ada_Version < Ada_05
1882 if Ekind
(Etype
(Formal
)) /= E_Anonymous_Access_Type
1883 or else Access_Checks_Suppressed
(Subp
)
1887 elsif Debug_Flag_J
then
1890 elsif not Comes_From_Source
(Prev
) then
1893 elsif Is_Entity_Name
(Prev
)
1894 and then Ekind
(Etype
(Prev
)) = E_Anonymous_Access_Type
1898 elsif Nkind
(Prev
) = N_Allocator
1899 or else Nkind
(Prev
) = N_Attribute_Reference
1903 -- Suppress null checks when passing to access parameters of Java
1904 -- subprograms. (Should this be done for other foreign conventions
1907 elsif Convention
(Subp
) = Convention_Java
then
1911 Install_Null_Excluding_Check
(Prev
);
1915 -- Perform appropriate validity checks on parameters that
1918 if Validity_Checks_On
then
1919 if (Ekind
(Formal
) = E_In_Parameter
1920 and then Validity_Check_In_Params
)
1922 (Ekind
(Formal
) = E_In_Out_Parameter
1923 and then Validity_Check_In_Out_Params
)
1925 -- If the actual is an indexed component of a packed
1926 -- type, it has not been expanded yet. It will be
1927 -- copied in the validity code that follows, and has
1928 -- to be expanded appropriately, so reanalyze it.
1930 if Nkind
(Actual
) = N_Indexed_Component
then
1931 Set_Analyzed
(Actual
, False);
1934 Ensure_Valid
(Actual
);
1938 -- For IN OUT and OUT parameters, ensure that subscripts are valid
1939 -- since this is a left side reference. We only do this for calls
1940 -- from the source program since we assume that compiler generated
1941 -- calls explicitly generate any required checks. We also need it
1942 -- only if we are doing standard validity checks, since clearly it
1943 -- is not needed if validity checks are off, and in subscript
1944 -- validity checking mode, all indexed components are checked with
1945 -- a call directly from Expand_N_Indexed_Component.
1947 if Comes_From_Source
(N
)
1948 and then Ekind
(Formal
) /= E_In_Parameter
1949 and then Validity_Checks_On
1950 and then Validity_Check_Default
1951 and then not Validity_Check_Subscripts
1953 Check_Valid_Lvalue_Subscripts
(Actual
);
1956 -- Mark any scalar OUT parameter that is a simple variable as no
1957 -- longer known to be valid (unless the type is always valid). This
1958 -- reflects the fact that if an OUT parameter is never set in a
1959 -- procedure, then it can become invalid on the procedure return.
1961 if Ekind
(Formal
) = E_Out_Parameter
1962 and then Is_Entity_Name
(Actual
)
1963 and then Ekind
(Entity
(Actual
)) = E_Variable
1964 and then not Is_Known_Valid
(Etype
(Actual
))
1966 Set_Is_Known_Valid
(Entity
(Actual
), False);
1969 -- For an OUT or IN OUT parameter, if the actual is an entity, then
1970 -- clear current values, since they can be clobbered. We are probably
1971 -- doing this in more places than we need to, but better safe than
1972 -- sorry when it comes to retaining bad current values!
1974 if Ekind
(Formal
) /= E_In_Parameter
1975 and then Is_Entity_Name
(Actual
)
1977 Kill_Current_Values
(Entity
(Actual
));
1980 -- If the formal is class wide and the actual is an aggregate, force
1981 -- evaluation so that the back end who does not know about class-wide
1982 -- type, does not generate a temporary of the wrong size.
1984 if not Is_Class_Wide_Type
(Etype
(Formal
)) then
1987 elsif Nkind
(Actual
) = N_Aggregate
1988 or else (Nkind
(Actual
) = N_Qualified_Expression
1989 and then Nkind
(Expression
(Actual
)) = N_Aggregate
)
1991 Force_Evaluation
(Actual
);
1994 -- In a remote call, if the formal is of a class-wide type, check
1995 -- that the actual meets the requirements described in E.4(18).
1998 and then Is_Class_Wide_Type
(Etype
(Formal
))
2000 Insert_Action
(Actual
,
2001 Make_Implicit_If_Statement
(N
,
2004 Get_Remotely_Callable
2005 (Duplicate_Subexpr_Move_Checks
(Actual
))),
2006 Then_Statements
=> New_List
(
2007 Make_Raise_Program_Error
(Loc
,
2008 Reason
=> PE_Illegal_RACW_E_4_18
))));
2011 -- This label is required when skipping extra actual generation for
2012 -- Unchecked_Union parameters.
2014 <<Skip_Extra_Actual_Generation
>>
2016 Next_Actual
(Actual
);
2017 Next_Formal
(Formal
);
2020 -- If we are expanding a rhs of an assignment we need to check if tag
2021 -- propagation is needed. You might expect this processing to be in
2022 -- Analyze_Assignment but has to be done earlier (bottom-up) because the
2023 -- assignment might be transformed to a declaration for an unconstrained
2024 -- value if the expression is classwide.
2026 if Nkind
(N
) = N_Function_Call
2027 and then Is_Tag_Indeterminate
(N
)
2028 and then Is_Entity_Name
(Name
(N
))
2031 Ass
: Node_Id
:= Empty
;
2034 if Nkind
(Parent
(N
)) = N_Assignment_Statement
then
2037 elsif Nkind
(Parent
(N
)) = N_Qualified_Expression
2038 and then Nkind
(Parent
(Parent
(N
))) = N_Assignment_Statement
2040 Ass
:= Parent
(Parent
(N
));
2042 elsif Nkind
(Parent
(N
)) = N_Explicit_Dereference
2043 and then Nkind
(Parent
(Parent
(N
))) = N_Assignment_Statement
2045 Ass
:= Parent
(Parent
(N
));
2049 and then Is_Class_Wide_Type
(Etype
(Name
(Ass
)))
2051 if Is_Access_Type
(Etype
(N
)) then
2052 if Designated_Type
(Etype
(N
)) /=
2053 Root_Type
(Etype
(Name
(Ass
)))
2056 ("tag-indeterminate expression "
2057 & " must have designated type& ('R'M 5.2 (6))",
2058 N
, Root_Type
(Etype
(Name
(Ass
))));
2060 Propagate_Tag
(Name
(Ass
), N
);
2063 elsif Etype
(N
) /= Root_Type
(Etype
(Name
(Ass
))) then
2065 ("tag-indeterminate expression must have type&"
2066 & "('R'M 5.2 (6))", N
, Root_Type
(Etype
(Name
(Ass
))));
2069 Propagate_Tag
(Name
(Ass
), N
);
2072 -- The call will be rewritten as a dispatching call, and
2073 -- expanded as such.
2080 -- Ada 2005 (AI-251): If some formal is a class-wide interface, expand
2081 -- it to point to the correct secondary virtual table
2083 if (Nkind
(N
) = N_Function_Call
2084 or else Nkind
(N
) = N_Procedure_Call_Statement
)
2085 and then CW_Interface_Formals_Present
2087 Expand_Interface_Actuals
(N
);
2090 -- Deals with Dispatch_Call if we still have a call, before expanding
2091 -- extra actuals since this will be done on the re-analysis of the
2092 -- dispatching call. Note that we do not try to shorten the actual
2093 -- list for a dispatching call, it would not make sense to do so.
2094 -- Expansion of dispatching calls is suppressed when Java_VM, because
2095 -- the JVM back end directly handles the generation of dispatching
2096 -- calls and would have to undo any expansion to an indirect call.
2098 if (Nkind
(N
) = N_Function_Call
2099 or else Nkind
(N
) = N_Procedure_Call_Statement
)
2100 and then Present
(Controlling_Argument
(N
))
2101 and then not Java_VM
2103 Expand_Dispatching_Call
(N
);
2105 -- The following return is worrisome. Is it really OK to
2106 -- skip all remaining processing in this procedure ???
2110 -- Similarly, expand calls to RCI subprograms on which pragma
2111 -- All_Calls_Remote applies. The rewriting will be reanalyzed
2112 -- later. Do this only when the call comes from source since we do
2113 -- not want such a rewritting to occur in expanded code.
2115 elsif Is_All_Remote_Call
(N
) then
2116 Expand_All_Calls_Remote_Subprogram_Call
(N
);
2118 -- Similarly, do not add extra actuals for an entry call whose entity
2119 -- is a protected procedure, or for an internal protected subprogram
2120 -- call, because it will be rewritten as a protected subprogram call
2121 -- and reanalyzed (see Expand_Protected_Subprogram_Call).
2123 elsif Is_Protected_Type
(Scope
(Subp
))
2124 and then (Ekind
(Subp
) = E_Procedure
2125 or else Ekind
(Subp
) = E_Function
)
2129 -- During that loop we gathered the extra actuals (the ones that
2130 -- correspond to Extra_Formals), so now they can be appended.
2133 while Is_Non_Empty_List
(Extra_Actuals
) loop
2134 Add_Actual_Parameter
(Remove_Head
(Extra_Actuals
));
2138 -- At this point we have all the actuals, so this is the point at
2139 -- which the various expansion activities for actuals is carried out.
2141 Expand_Actuals
(N
, Subp
);
2143 -- If the subprogram is a renaming, or if it is inherited, replace it
2144 -- in the call with the name of the actual subprogram being called.
2145 -- If this is a dispatching call, the run-time decides what to call.
2146 -- The Alias attribute does not apply to entries.
2148 if Nkind
(N
) /= N_Entry_Call_Statement
2149 and then No
(Controlling_Argument
(N
))
2150 and then Present
(Parent_Subp
)
2152 if Present
(Inherited_From_Formal
(Subp
)) then
2153 Parent_Subp
:= Inherited_From_Formal
(Subp
);
2155 while Present
(Alias
(Parent_Subp
)) loop
2156 Parent_Subp
:= Alias
(Parent_Subp
);
2160 -- The below setting of Entity is suspect, see F109-018 discussion???
2162 Set_Entity
(Name
(N
), Parent_Subp
);
2164 if Is_Abstract
(Parent_Subp
)
2165 and then not In_Instance
2168 ("cannot call abstract subprogram &!", Name
(N
), Parent_Subp
);
2171 -- Add an explicit conversion for parameter of the derived type.
2172 -- This is only done for scalar and access in-parameters. Others
2173 -- have been expanded in expand_actuals.
2175 Formal
:= First_Formal
(Subp
);
2176 Parent_Formal
:= First_Formal
(Parent_Subp
);
2177 Actual
:= First_Actual
(N
);
2179 -- It is not clear that conversion is needed for intrinsic
2180 -- subprograms, but it certainly is for those that are user-
2181 -- defined, and that can be inherited on derivation, namely
2182 -- unchecked conversion and deallocation.
2183 -- General case needs study ???
2185 if not Is_Intrinsic_Subprogram
(Parent_Subp
)
2186 or else Is_Generic_Instance
(Parent_Subp
)
2188 while Present
(Formal
) loop
2189 if Etype
(Formal
) /= Etype
(Parent_Formal
)
2190 and then Is_Scalar_Type
(Etype
(Formal
))
2191 and then Ekind
(Formal
) = E_In_Parameter
2193 not Subtypes_Statically_Match
2194 (Etype
(Parent_Formal
), Etype
(Actual
))
2195 and then not Raises_Constraint_Error
(Actual
)
2198 OK_Convert_To
(Etype
(Parent_Formal
),
2199 Relocate_Node
(Actual
)));
2202 Resolve
(Actual
, Etype
(Parent_Formal
));
2203 Enable_Range_Check
(Actual
);
2205 elsif Is_Access_Type
(Etype
(Formal
))
2206 and then Base_Type
(Etype
(Parent_Formal
)) /=
2207 Base_Type
(Etype
(Actual
))
2209 if Ekind
(Formal
) /= E_In_Parameter
then
2211 Convert_To
(Etype
(Parent_Formal
),
2212 Relocate_Node
(Actual
)));
2215 Resolve
(Actual
, Etype
(Parent_Formal
));
2218 Ekind
(Etype
(Parent_Formal
)) = E_Anonymous_Access_Type
2219 and then Designated_Type
(Etype
(Parent_Formal
))
2221 Designated_Type
(Etype
(Actual
))
2222 and then not Is_Controlling_Formal
(Formal
)
2224 -- This unchecked conversion is not necessary unless
2225 -- inlining is enabled, because in that case the type
2226 -- mismatch may become visible in the body about to be
2230 Unchecked_Convert_To
(Etype
(Parent_Formal
),
2231 Relocate_Node
(Actual
)));
2234 Resolve
(Actual
, Etype
(Parent_Formal
));
2238 Next_Formal
(Formal
);
2239 Next_Formal
(Parent_Formal
);
2240 Next_Actual
(Actual
);
2245 Subp
:= Parent_Subp
;
2248 -- Check for violation of No_Abort_Statements
2250 if Is_RTE
(Subp
, RE_Abort_Task
) then
2251 Check_Restriction
(No_Abort_Statements
, N
);
2253 -- Check for violation of No_Dynamic_Attachment
2255 elsif RTU_Loaded
(Ada_Interrupts
)
2256 and then (Is_RTE
(Subp
, RE_Is_Reserved
) or else
2257 Is_RTE
(Subp
, RE_Is_Attached
) or else
2258 Is_RTE
(Subp
, RE_Current_Handler
) or else
2259 Is_RTE
(Subp
, RE_Attach_Handler
) or else
2260 Is_RTE
(Subp
, RE_Exchange_Handler
) or else
2261 Is_RTE
(Subp
, RE_Detach_Handler
) or else
2262 Is_RTE
(Subp
, RE_Reference
))
2264 Check_Restriction
(No_Dynamic_Attachment
, N
);
2267 -- Deal with case where call is an explicit dereference
2269 if Nkind
(Name
(N
)) = N_Explicit_Dereference
then
2271 -- Handle case of access to protected subprogram type
2273 if Ekind
(Base_Type
(Etype
(Prefix
(Name
(N
))))) =
2274 E_Access_Protected_Subprogram_Type
2276 -- If this is a call through an access to protected operation,
2277 -- the prefix has the form (object'address, operation'access).
2278 -- Rewrite as a for other protected calls: the object is the
2279 -- first parameter of the list of actuals.
2286 Ptr
: constant Node_Id
:= Prefix
(Name
(N
));
2288 T
: constant Entity_Id
:=
2289 Equivalent_Type
(Base_Type
(Etype
(Ptr
)));
2291 D_T
: constant Entity_Id
:=
2292 Designated_Type
(Base_Type
(Etype
(Ptr
)));
2296 Make_Selected_Component
(Loc
,
2297 Prefix
=> Unchecked_Convert_To
(T
, Ptr
),
2299 New_Occurrence_Of
(First_Entity
(T
), Loc
));
2302 Make_Selected_Component
(Loc
,
2303 Prefix
=> Unchecked_Convert_To
(T
, Ptr
),
2305 New_Occurrence_Of
(Next_Entity
(First_Entity
(T
)), Loc
));
2308 Make_Explicit_Dereference
(Loc
,
2311 if Present
(Parameter_Associations
(N
)) then
2312 Parm
:= Parameter_Associations
(N
);
2317 Prepend
(Obj
, Parm
);
2319 if Etype
(D_T
) = Standard_Void_Type
then
2321 Make_Procedure_Call_Statement
(Loc
,
2323 Parameter_Associations
=> Parm
);
2326 Make_Function_Call
(Loc
,
2328 Parameter_Associations
=> Parm
);
2331 Set_First_Named_Actual
(Call
, First_Named_Actual
(N
));
2332 Set_Etype
(Call
, Etype
(D_T
));
2334 -- We do not re-analyze the call to avoid infinite recursion.
2335 -- We analyze separately the prefix and the object, and set
2336 -- the checks on the prefix that would otherwise be emitted
2337 -- when resolving a call.
2341 Apply_Access_Check
(Nam
);
2348 -- If this is a call to an intrinsic subprogram, then perform the
2349 -- appropriate expansion to the corresponding tree node and we
2350 -- are all done (since after that the call is gone!)
2352 -- In the case where the intrinsic is to be processed by the back end,
2353 -- the call to Expand_Intrinsic_Call will do nothing, which is fine,
2354 -- since the idea in this case is to pass the call unchanged.
2356 if Is_Intrinsic_Subprogram
(Subp
) then
2357 Expand_Intrinsic_Call
(N
, Subp
);
2361 if Ekind
(Subp
) = E_Function
2362 or else Ekind
(Subp
) = E_Procedure
2364 if Is_Inlined
(Subp
) then
2366 Inlined_Subprogram
: declare
2368 Must_Inline
: Boolean := False;
2369 Spec
: constant Node_Id
:= Unit_Declaration_Node
(Subp
);
2370 Scop
: constant Entity_Id
:= Scope
(Subp
);
2372 function In_Unfrozen_Instance
return Boolean;
2373 -- If the subprogram comes from an instance in the same
2374 -- unit, and the instance is not yet frozen, inlining might
2375 -- trigger order-of-elaboration problems in gigi.
2377 --------------------------
2378 -- In_Unfrozen_Instance --
2379 --------------------------
2381 function In_Unfrozen_Instance
return Boolean is
2387 and then S
/= Standard_Standard
2389 if Is_Generic_Instance
(S
)
2390 and then Present
(Freeze_Node
(S
))
2391 and then not Analyzed
(Freeze_Node
(S
))
2400 end In_Unfrozen_Instance
;
2402 -- Start of processing for Inlined_Subprogram
2405 -- Verify that the body to inline has already been seen, and
2406 -- that if the body is in the current unit the inlining does
2407 -- not occur earlier. This avoids order-of-elaboration problems
2410 -- This should be documented in sinfo/einfo ???
2413 or else Nkind
(Spec
) /= N_Subprogram_Declaration
2414 or else No
(Body_To_Inline
(Spec
))
2416 Must_Inline
:= False;
2418 -- If this an inherited function that returns a private
2419 -- type, do not inline if the full view is an unconstrained
2420 -- array, because such calls cannot be inlined.
2422 elsif Present
(Orig_Subp
)
2423 and then Is_Array_Type
(Etype
(Orig_Subp
))
2424 and then not Is_Constrained
(Etype
(Orig_Subp
))
2426 Must_Inline
:= False;
2428 elsif In_Unfrozen_Instance
then
2429 Must_Inline
:= False;
2432 Bod
:= Body_To_Inline
(Spec
);
2434 if (In_Extended_Main_Code_Unit
(N
)
2435 or else In_Extended_Main_Code_Unit
(Parent
(N
))
2436 or else Is_Always_Inlined
(Subp
))
2437 and then (not In_Same_Extended_Unit
(Sloc
(Bod
), Loc
)
2439 Earlier_In_Extended_Unit
(Sloc
(Bod
), Loc
))
2441 Must_Inline
:= True;
2443 -- If we are compiling a package body that is not the main
2444 -- unit, it must be for inlining/instantiation purposes,
2445 -- in which case we inline the call to insure that the same
2446 -- temporaries are generated when compiling the body by
2447 -- itself. Otherwise link errors can occur.
2449 -- If the function being called is itself in the main unit,
2450 -- we cannot inline, because there is a risk of double
2451 -- elaboration and/or circularity: the inlining can make
2452 -- visible a private entity in the body of the main unit,
2453 -- that gigi will see before its sees its proper definition.
2455 elsif not (In_Extended_Main_Code_Unit
(N
))
2456 and then In_Package_Body
2458 Must_Inline
:= not In_Extended_Main_Source_Unit
(Subp
);
2463 Expand_Inlined_Call
(N
, Subp
, Orig_Subp
);
2466 -- Let the back end handle it
2468 Add_Inlined_Body
(Subp
);
2470 if Front_End_Inlining
2471 and then Nkind
(Spec
) = N_Subprogram_Declaration
2472 and then (In_Extended_Main_Code_Unit
(N
))
2473 and then No
(Body_To_Inline
(Spec
))
2474 and then not Has_Completion
(Subp
)
2475 and then In_Same_Extended_Unit
(Sloc
(Spec
), Loc
)
2478 ("cannot inline& (body not seen yet)?",
2482 end Inlined_Subprogram
;
2486 -- Check for a protected subprogram. This is either an intra-object
2487 -- call, or a protected function call. Protected procedure calls are
2488 -- rewritten as entry calls and handled accordingly.
2490 -- In Ada 2005, this may be an indirect call to an access parameter
2491 -- that is an access_to_subprogram. In that case the anonymous type
2492 -- has a scope that is a protected operation, but the call is a
2495 Scop
:= Scope
(Subp
);
2497 if Nkind
(N
) /= N_Entry_Call_Statement
2498 and then Is_Protected_Type
(Scop
)
2499 and then Ekind
(Subp
) /= E_Subprogram_Type
2501 -- If the call is an internal one, it is rewritten as a call to
2502 -- to the corresponding unprotected subprogram.
2504 Expand_Protected_Subprogram_Call
(N
, Subp
, Scop
);
2507 -- Functions returning controlled objects need special attention
2509 if Controlled_Type
(Etype
(Subp
))
2510 and then not Is_Inherently_Limited_Type
(Etype
(Subp
))
2512 Expand_Ctrl_Function_Call
(N
);
2515 -- Test for First_Optional_Parameter, and if so, truncate parameter
2516 -- list if there are optional parameters at the trailing end.
2517 -- Note we never delete procedures for call via a pointer.
2519 if (Ekind
(Subp
) = E_Procedure
or else Ekind
(Subp
) = E_Function
)
2520 and then Present
(First_Optional_Parameter
(Subp
))
2523 Last_Keep_Arg
: Node_Id
;
2526 -- Last_Keep_Arg will hold the last actual that should be
2527 -- retained. If it remains empty at the end, it means that
2528 -- all parameters are optional.
2530 Last_Keep_Arg
:= Empty
;
2532 -- Find first optional parameter, must be present since we
2533 -- checked the validity of the parameter before setting it.
2535 Formal
:= First_Formal
(Subp
);
2536 Actual
:= First_Actual
(N
);
2537 while Formal
/= First_Optional_Parameter
(Subp
) loop
2538 Last_Keep_Arg
:= Actual
;
2539 Next_Formal
(Formal
);
2540 Next_Actual
(Actual
);
2543 -- We have Formal and Actual pointing to the first potentially
2544 -- droppable argument. We can drop all the trailing arguments
2545 -- whose actual matches the default. Note that we know that all
2546 -- remaining formals have defaults, because we checked that this
2547 -- requirement was met before setting First_Optional_Parameter.
2549 -- We use Fully_Conformant_Expressions to check for identity
2550 -- between formals and actuals, which may miss some cases, but
2551 -- on the other hand, this is only an optimization (if we fail
2552 -- to truncate a parameter it does not affect functionality).
2553 -- So if the default is 3 and the actual is 1+2, we consider
2554 -- them unequal, which hardly seems worrisome.
2556 while Present
(Formal
) loop
2557 if not Fully_Conformant_Expressions
2558 (Actual
, Default_Value
(Formal
))
2560 Last_Keep_Arg
:= Actual
;
2563 Next_Formal
(Formal
);
2564 Next_Actual
(Actual
);
2567 -- If no arguments, delete entire list, this is the easy case
2569 if No
(Last_Keep_Arg
) then
2570 while Is_Non_Empty_List
(Parameter_Associations
(N
)) loop
2571 Delete_Tree
(Remove_Head
(Parameter_Associations
(N
)));
2574 Set_Parameter_Associations
(N
, No_List
);
2575 Set_First_Named_Actual
(N
, Empty
);
2577 -- Case where at the last retained argument is positional. This
2578 -- is also an easy case, since the retained arguments are already
2579 -- in the right form, and we don't need to worry about the order
2580 -- of arguments that get eliminated.
2582 elsif Is_List_Member
(Last_Keep_Arg
) then
2583 while Present
(Next
(Last_Keep_Arg
)) loop
2584 Delete_Tree
(Remove_Next
(Last_Keep_Arg
));
2587 Set_First_Named_Actual
(N
, Empty
);
2589 -- This is the annoying case where the last retained argument
2590 -- is a named parameter. Since the original arguments are not
2591 -- in declaration order, we may have to delete some fairly
2592 -- random collection of arguments.
2600 pragma Warnings
(Off
, Discard
);
2603 -- First step, remove all the named parameters from the
2604 -- list (they are still chained using First_Named_Actual
2605 -- and Next_Named_Actual, so we have not lost them!)
2607 Temp
:= First
(Parameter_Associations
(N
));
2609 -- Case of all parameters named, remove them all
2611 if Nkind
(Temp
) = N_Parameter_Association
then
2612 while Is_Non_Empty_List
(Parameter_Associations
(N
)) loop
2613 Temp
:= Remove_Head
(Parameter_Associations
(N
));
2616 -- Case of mixed positional/named, remove named parameters
2619 while Nkind
(Next
(Temp
)) /= N_Parameter_Association
loop
2623 while Present
(Next
(Temp
)) loop
2624 Discard
:= Remove_Next
(Temp
);
2628 -- Now we loop through the named parameters, till we get
2629 -- to the last one to be retained, adding them to the list.
2630 -- Note that the Next_Named_Actual list does not need to be
2631 -- touched since we are only reordering them on the actual
2632 -- parameter association list.
2634 Passoc
:= Parent
(First_Named_Actual
(N
));
2636 Temp
:= Relocate_Node
(Passoc
);
2638 (Parameter_Associations
(N
), Temp
);
2640 Last_Keep_Arg
= Explicit_Actual_Parameter
(Passoc
);
2641 Passoc
:= Parent
(Next_Named_Actual
(Passoc
));
2644 Set_Next_Named_Actual
(Temp
, Empty
);
2647 Temp
:= Next_Named_Actual
(Passoc
);
2648 exit when No
(Temp
);
2649 Set_Next_Named_Actual
2650 (Passoc
, Next_Named_Actual
(Parent
(Temp
)));
2658 -- Special processing for Ada 2005 AI-329, which requires a call to
2659 -- Raise_Exception to raise Constraint_Error if the Exception_Id is
2660 -- null. Note that we never need to do this in GNAT mode, or if the
2661 -- parameter to Raise_Exception is a use of Identity, since in these
2662 -- cases we know that the parameter is never null.
2664 if Ada_Version
>= Ada_05
2665 and then not GNAT_Mode
2666 and then Is_RTE
(Subp
, RE_Raise_Exception
)
2667 and then (Nkind
(First_Actual
(N
)) /= N_Attribute_Reference
2668 or else Attribute_Name
(First_Actual
(N
)) /= Name_Identity
)
2671 RCE
: constant Node_Id
:=
2672 Make_Raise_Constraint_Error
(Loc
,
2673 Reason
=> CE_Null_Exception_Id
);
2675 Insert_After
(N
, RCE
);
2681 --------------------------
2682 -- Expand_Inlined_Call --
2683 --------------------------
2685 procedure Expand_Inlined_Call
2688 Orig_Subp
: Entity_Id
)
2690 Loc
: constant Source_Ptr
:= Sloc
(N
);
2691 Is_Predef
: constant Boolean :=
2692 Is_Predefined_File_Name
2693 (Unit_File_Name
(Get_Source_Unit
(Subp
)));
2694 Orig_Bod
: constant Node_Id
:=
2695 Body_To_Inline
(Unit_Declaration_Node
(Subp
));
2700 Decls
: constant List_Id
:= New_List
;
2701 Exit_Lab
: Entity_Id
:= Empty
;
2708 Ret_Type
: Entity_Id
;
2712 Temp_Typ
: Entity_Id
;
2714 Is_Unc
: constant Boolean :=
2715 Is_Array_Type
(Etype
(Subp
))
2716 and then not Is_Constrained
(Etype
(Subp
));
2717 -- If the type returned by the function is unconstrained and the
2718 -- call can be inlined, special processing is required.
2720 procedure Make_Exit_Label
;
2721 -- Build declaration for exit label to be used in Return statements
2723 function Process_Formals
(N
: Node_Id
) return Traverse_Result
;
2724 -- Replace occurrence of a formal with the corresponding actual, or
2725 -- the thunk generated for it.
2727 function Process_Sloc
(Nod
: Node_Id
) return Traverse_Result
;
2728 -- If the call being expanded is that of an internal subprogram,
2729 -- set the sloc of the generated block to that of the call itself,
2730 -- so that the expansion is skipped by the -next- command in gdb.
2731 -- Same processing for a subprogram in a predefined file, e.g.
2732 -- Ada.Tags. If Debug_Generated_Code is true, suppress this change
2733 -- to simplify our own development.
2735 procedure Rewrite_Function_Call
(N
: Node_Id
; Blk
: Node_Id
);
2736 -- If the function body is a single expression, replace call with
2737 -- expression, else insert block appropriately.
2739 procedure Rewrite_Procedure_Call
(N
: Node_Id
; Blk
: Node_Id
);
2740 -- If procedure body has no local variables, inline body without
2741 -- creating block, otherwise rewrite call with block.
2743 function Formal_Is_Used_Once
(Formal
: Entity_Id
) return Boolean;
2744 -- Determine whether a formal parameter is used only once in Orig_Bod
2746 ---------------------
2747 -- Make_Exit_Label --
2748 ---------------------
2750 procedure Make_Exit_Label
is
2752 -- Create exit label for subprogram if one does not exist yet
2754 if No
(Exit_Lab
) then
2756 Make_Identifier
(Loc
,
2757 Chars
=> New_Internal_Name
('L'));
2759 Make_Defining_Identifier
(Loc
, Chars
(Lab_Id
)));
2760 Exit_Lab
:= Make_Label
(Loc
, Lab_Id
);
2763 Make_Implicit_Label_Declaration
(Loc
,
2764 Defining_Identifier
=> Entity
(Lab_Id
),
2765 Label_Construct
=> Exit_Lab
);
2767 end Make_Exit_Label
;
2769 ---------------------
2770 -- Process_Formals --
2771 ---------------------
2773 function Process_Formals
(N
: Node_Id
) return Traverse_Result
is
2779 if Is_Entity_Name
(N
)
2780 and then Present
(Entity
(N
))
2785 and then Scope
(E
) = Subp
2787 A
:= Renamed_Object
(E
);
2789 -- Rewrite the occurrence of the formal into an occurrence of
2790 -- the actual. Also establish visibility on the proper view of
2791 -- the actual's subtype for the body's context (if the actual's
2792 -- subtype is private at the call point but its full view is
2793 -- visible to the body, then the inlined tree here must be
2794 -- analyzed with the full view).
2796 if Is_Entity_Name
(A
) then
2797 Rewrite
(N
, New_Occurrence_Of
(Entity
(A
), Loc
));
2798 Check_Private_View
(N
);
2800 elsif Nkind
(A
) = N_Defining_Identifier
then
2801 Rewrite
(N
, New_Occurrence_Of
(A
, Loc
));
2802 Check_Private_View
(N
);
2804 else -- numeric literal
2805 Rewrite
(N
, New_Copy
(A
));
2811 elsif Nkind
(N
) = N_Return_Statement
then
2813 if No
(Expression
(N
)) then
2815 Rewrite
(N
, Make_Goto_Statement
(Loc
,
2816 Name
=> New_Copy
(Lab_Id
)));
2819 if Nkind
(Parent
(N
)) = N_Handled_Sequence_Of_Statements
2820 and then Nkind
(Parent
(Parent
(N
))) = N_Subprogram_Body
2822 -- Function body is a single expression. No need for
2828 Num_Ret
:= Num_Ret
+ 1;
2832 -- Because of the presence of private types, the views of the
2833 -- expression and the context may be different, so place an
2834 -- unchecked conversion to the context type to avoid spurious
2835 -- errors, eg. when the expression is a numeric literal and
2836 -- the context is private. If the expression is an aggregate,
2837 -- use a qualified expression, because an aggregate is not a
2838 -- legal argument of a conversion.
2840 if Nkind
(Expression
(N
)) = N_Aggregate
2841 or else Nkind
(Expression
(N
)) = N_Null
2844 Make_Qualified_Expression
(Sloc
(N
),
2845 Subtype_Mark
=> New_Occurrence_Of
(Ret_Type
, Sloc
(N
)),
2846 Expression
=> Relocate_Node
(Expression
(N
)));
2849 Unchecked_Convert_To
2850 (Ret_Type
, Relocate_Node
(Expression
(N
)));
2853 if Nkind
(Targ
) = N_Defining_Identifier
then
2855 Make_Assignment_Statement
(Loc
,
2856 Name
=> New_Occurrence_Of
(Targ
, Loc
),
2857 Expression
=> Ret
));
2860 Make_Assignment_Statement
(Loc
,
2861 Name
=> New_Copy
(Targ
),
2862 Expression
=> Ret
));
2865 Set_Assignment_OK
(Name
(N
));
2867 if Present
(Exit_Lab
) then
2869 Make_Goto_Statement
(Loc
,
2870 Name
=> New_Copy
(Lab_Id
)));
2876 -- Remove pragma Unreferenced since it may refer to formals that
2877 -- are not visible in the inlined body, and in any case we will
2878 -- not be posting warnings on the inlined body so it is unneeded.
2880 elsif Nkind
(N
) = N_Pragma
2881 and then Chars
(N
) = Name_Unreferenced
2883 Rewrite
(N
, Make_Null_Statement
(Sloc
(N
)));
2889 end Process_Formals
;
2891 procedure Replace_Formals
is new Traverse_Proc
(Process_Formals
);
2897 function Process_Sloc
(Nod
: Node_Id
) return Traverse_Result
is
2899 if not Debug_Generated_Code
then
2900 Set_Sloc
(Nod
, Sloc
(N
));
2901 Set_Comes_From_Source
(Nod
, False);
2907 procedure Reset_Slocs
is new Traverse_Proc
(Process_Sloc
);
2909 ---------------------------
2910 -- Rewrite_Function_Call --
2911 ---------------------------
2913 procedure Rewrite_Function_Call
(N
: Node_Id
; Blk
: Node_Id
) is
2914 HSS
: constant Node_Id
:= Handled_Statement_Sequence
(Blk
);
2915 Fst
: constant Node_Id
:= First
(Statements
(HSS
));
2918 -- Optimize simple case: function body is a single return statement,
2919 -- which has been expanded into an assignment.
2921 if Is_Empty_List
(Declarations
(Blk
))
2922 and then Nkind
(Fst
) = N_Assignment_Statement
2923 and then No
(Next
(Fst
))
2926 -- The function call may have been rewritten as the temporary
2927 -- that holds the result of the call, in which case remove the
2928 -- now useless declaration.
2930 if Nkind
(N
) = N_Identifier
2931 and then Nkind
(Parent
(Entity
(N
))) = N_Object_Declaration
2933 Rewrite
(Parent
(Entity
(N
)), Make_Null_Statement
(Loc
));
2936 Rewrite
(N
, Expression
(Fst
));
2938 elsif Nkind
(N
) = N_Identifier
2939 and then Nkind
(Parent
(Entity
(N
))) = N_Object_Declaration
2941 -- The block assigns the result of the call to the temporary
2943 Insert_After
(Parent
(Entity
(N
)), Blk
);
2945 elsif Nkind
(Parent
(N
)) = N_Assignment_Statement
2947 (Is_Entity_Name
(Name
(Parent
(N
)))
2949 (Nkind
(Name
(Parent
(N
))) = N_Explicit_Dereference
2950 and then Is_Entity_Name
(Prefix
(Name
(Parent
(N
))))))
2952 -- Replace assignment with the block
2955 Original_Assignment
: constant Node_Id
:= Parent
(N
);
2958 -- Preserve the original assignment node to keep the complete
2959 -- assignment subtree consistent enough for Analyze_Assignment
2960 -- to proceed (specifically, the original Lhs node must still
2961 -- have an assignment statement as its parent).
2963 -- We cannot rely on Original_Node to go back from the block
2964 -- node to the assignment node, because the assignment might
2965 -- already be a rewrite substitution.
2967 Discard_Node
(Relocate_Node
(Original_Assignment
));
2968 Rewrite
(Original_Assignment
, Blk
);
2971 elsif Nkind
(Parent
(N
)) = N_Object_Declaration
then
2972 Set_Expression
(Parent
(N
), Empty
);
2973 Insert_After
(Parent
(N
), Blk
);
2976 Insert_Before
(Parent
(N
), Blk
);
2978 end Rewrite_Function_Call
;
2980 ----------------------------
2981 -- Rewrite_Procedure_Call --
2982 ----------------------------
2984 procedure Rewrite_Procedure_Call
(N
: Node_Id
; Blk
: Node_Id
) is
2985 HSS
: constant Node_Id
:= Handled_Statement_Sequence
(Blk
);
2987 -- If there is a transient scope for N, this will be the scope of the
2988 -- actions for N, and the statements in Blk need to be within this
2989 -- scope. For example, they need to have visibility on the constant
2990 -- declarations created for the formals.
2992 -- If N needs no transient scope, and if there are no declarations in
2993 -- the inlined body, we can do a little optimization and insert the
2994 -- statements for the body directly after N, and rewrite N to a
2995 -- null statement, instead of rewriting N into a full-blown block
2998 if not Scope_Is_Transient
2999 and then Is_Empty_List
(Declarations
(Blk
))
3001 Insert_List_After
(N
, Statements
(HSS
));
3002 Rewrite
(N
, Make_Null_Statement
(Loc
));
3006 end Rewrite_Procedure_Call
;
3008 -------------------------
3009 -- Formal_Is_Used_Once --
3010 -------------------------
3012 function Formal_Is_Used_Once
(Formal
: Entity_Id
) return Boolean is
3013 Use_Counter
: Int
:= 0;
3015 function Count_Uses
(N
: Node_Id
) return Traverse_Result
;
3016 -- Traverse the tree and count the uses of the formal parameter.
3017 -- In this case, for optimization purposes, we do not need to
3018 -- continue the traversal once more than one use is encountered.
3024 function Count_Uses
(N
: Node_Id
) return Traverse_Result
is
3026 -- The original node is an identifier
3028 if Nkind
(N
) = N_Identifier
3029 and then Present
(Entity
(N
))
3031 -- Original node's entity points to the one in the copied body
3033 and then Nkind
(Entity
(N
)) = N_Identifier
3034 and then Present
(Entity
(Entity
(N
)))
3036 -- The entity of the copied node is the formal parameter
3038 and then Entity
(Entity
(N
)) = Formal
3040 Use_Counter
:= Use_Counter
+ 1;
3042 if Use_Counter
> 1 then
3044 -- Denote more than one use and abandon the traversal
3055 procedure Count_Formal_Uses
is new Traverse_Proc
(Count_Uses
);
3057 -- Start of processing for Formal_Is_Used_Once
3060 Count_Formal_Uses
(Orig_Bod
);
3061 return Use_Counter
= 1;
3062 end Formal_Is_Used_Once
;
3064 -- Start of processing for Expand_Inlined_Call
3067 -- Check for special case of To_Address call, and if so, just do an
3068 -- unchecked conversion instead of expanding the call. Not only is this
3069 -- more efficient, but it also avoids problem with order of elaboration
3070 -- when address clauses are inlined (address expression elaborated at
3073 if Subp
= RTE
(RE_To_Address
) then
3075 Unchecked_Convert_To
3077 Relocate_Node
(First_Actual
(N
))));
3081 -- Check for an illegal attempt to inline a recursive procedure. If the
3082 -- subprogram has parameters this is detected when trying to supply a
3083 -- binding for parameters that already have one. For parameterless
3084 -- subprograms this must be done explicitly.
3086 if In_Open_Scopes
(Subp
) then
3087 Error_Msg_N
("call to recursive subprogram cannot be inlined?", N
);
3088 Set_Is_Inlined
(Subp
, False);
3092 if Nkind
(Orig_Bod
) = N_Defining_Identifier
3093 or else Nkind
(Orig_Bod
) = N_Defining_Operator_Symbol
3095 -- Subprogram is a renaming_as_body. Calls appearing after the
3096 -- renaming can be replaced with calls to the renamed entity
3097 -- directly, because the subprograms are subtype conformant. If
3098 -- the renamed subprogram is an inherited operation, we must redo
3099 -- the expansion because implicit conversions may be needed.
3101 Set_Name
(N
, New_Occurrence_Of
(Orig_Bod
, Loc
));
3103 if Present
(Alias
(Orig_Bod
)) then
3110 -- Use generic machinery to copy body of inlined subprogram, as if it
3111 -- were an instantiation, resetting source locations appropriately, so
3112 -- that nested inlined calls appear in the main unit.
3114 Save_Env
(Subp
, Empty
);
3115 Set_Copied_Sloc_For_Inlined_Body
(N
, Defining_Entity
(Orig_Bod
));
3117 Bod
:= Copy_Generic_Node
(Orig_Bod
, Empty
, Instantiating
=> True);
3119 Make_Block_Statement
(Loc
,
3120 Declarations
=> Declarations
(Bod
),
3121 Handled_Statement_Sequence
=> Handled_Statement_Sequence
(Bod
));
3123 if No
(Declarations
(Bod
)) then
3124 Set_Declarations
(Blk
, New_List
);
3127 -- For the unconstrained case, capture the name of the local
3128 -- variable that holds the result. This must be the first declaration
3129 -- in the block, because its bounds cannot depend on local variables.
3130 -- Otherwise there is no way to declare the result outside of the
3131 -- block. Needless to say, in general the bounds will depend on the
3132 -- actuals in the call.
3135 Targ1
:= Defining_Identifier
(First
(Declarations
(Blk
)));
3138 -- If this is a derived function, establish the proper return type
3140 if Present
(Orig_Subp
)
3141 and then Orig_Subp
/= Subp
3143 Ret_Type
:= Etype
(Orig_Subp
);
3145 Ret_Type
:= Etype
(Subp
);
3148 -- Create temporaries for the actuals that are expressions, or that
3149 -- are scalars and require copying to preserve semantics.
3151 F
:= First_Formal
(Subp
);
3152 A
:= First_Actual
(N
);
3153 while Present
(F
) loop
3154 if Present
(Renamed_Object
(F
)) then
3155 Error_Msg_N
("cannot inline call to recursive subprogram", N
);
3159 -- If the argument may be a controlling argument in a call within
3160 -- the inlined body, we must preserve its classwide nature to insure
3161 -- that dynamic dispatching take place subsequently. If the formal
3162 -- has a constraint it must be preserved to retain the semantics of
3165 if Is_Class_Wide_Type
(Etype
(F
))
3166 or else (Is_Access_Type
(Etype
(F
))
3168 Is_Class_Wide_Type
(Designated_Type
(Etype
(F
))))
3170 Temp_Typ
:= Etype
(F
);
3172 elsif Base_Type
(Etype
(F
)) = Base_Type
(Etype
(A
))
3173 and then Etype
(F
) /= Base_Type
(Etype
(F
))
3175 Temp_Typ
:= Etype
(F
);
3178 Temp_Typ
:= Etype
(A
);
3181 -- If the actual is a simple name or a literal, no need to
3182 -- create a temporary, object can be used directly.
3184 if (Is_Entity_Name
(A
)
3186 (not Is_Scalar_Type
(Etype
(A
))
3187 or else Ekind
(Entity
(A
)) = E_Enumeration_Literal
))
3189 -- When the actual is an identifier and the corresponding formal
3190 -- is used only once in the original body, the formal can be
3191 -- substituted directly with the actual parameter.
3193 or else (Nkind
(A
) = N_Identifier
3194 and then Formal_Is_Used_Once
(F
))
3196 or else Nkind
(A
) = N_Real_Literal
3197 or else Nkind
(A
) = N_Integer_Literal
3198 or else Nkind
(A
) = N_Character_Literal
3200 if Etype
(F
) /= Etype
(A
) then
3202 (F
, Unchecked_Convert_To
(Etype
(F
), Relocate_Node
(A
)));
3204 Set_Renamed_Object
(F
, A
);
3209 Make_Defining_Identifier
(Loc
,
3210 Chars
=> New_Internal_Name
('C'));
3212 -- If the actual for an in/in-out parameter is a view conversion,
3213 -- make it into an unchecked conversion, given that an untagged
3214 -- type conversion is not a proper object for a renaming.
3216 -- In-out conversions that involve real conversions have already
3217 -- been transformed in Expand_Actuals.
3219 if Nkind
(A
) = N_Type_Conversion
3220 and then Ekind
(F
) /= E_In_Parameter
3223 Make_Unchecked_Type_Conversion
(Loc
,
3224 Subtype_Mark
=> New_Occurrence_Of
(Etype
(F
), Loc
),
3225 Expression
=> Relocate_Node
(Expression
(A
)));
3227 elsif Etype
(F
) /= Etype
(A
) then
3228 New_A
:= Unchecked_Convert_To
(Etype
(F
), Relocate_Node
(A
));
3229 Temp_Typ
:= Etype
(F
);
3232 New_A
:= Relocate_Node
(A
);
3235 Set_Sloc
(New_A
, Sloc
(N
));
3237 -- If the actual has a by-reference type, it cannot be copied, so
3238 -- its value is captured in a renaming declaration. Otherwise
3239 -- declare a local constant initalized with the actual.
3241 if Ekind
(F
) = E_In_Parameter
3242 and then not Is_Limited_Type
(Etype
(A
))
3243 and then not Is_Tagged_Type
(Etype
(A
))
3246 Make_Object_Declaration
(Loc
,
3247 Defining_Identifier
=> Temp
,
3248 Constant_Present
=> True,
3249 Object_Definition
=> New_Occurrence_Of
(Temp_Typ
, Loc
),
3250 Expression
=> New_A
);
3253 Make_Object_Renaming_Declaration
(Loc
,
3254 Defining_Identifier
=> Temp
,
3255 Subtype_Mark
=> New_Occurrence_Of
(Temp_Typ
, Loc
),
3259 Append
(Decl
, Decls
);
3260 Set_Renamed_Object
(F
, Temp
);
3267 -- Establish target of function call. If context is not assignment or
3268 -- declaration, create a temporary as a target. The declaration for
3269 -- the temporary may be subsequently optimized away if the body is a
3270 -- single expression, or if the left-hand side of the assignment is
3271 -- simple enough, i.e. an entity or an explicit dereference of one.
3273 if Ekind
(Subp
) = E_Function
then
3274 if Nkind
(Parent
(N
)) = N_Assignment_Statement
3275 and then Is_Entity_Name
(Name
(Parent
(N
)))
3277 Targ
:= Name
(Parent
(N
));
3279 elsif Nkind
(Parent
(N
)) = N_Assignment_Statement
3280 and then Nkind
(Name
(Parent
(N
))) = N_Explicit_Dereference
3281 and then Is_Entity_Name
(Prefix
(Name
(Parent
(N
))))
3283 Targ
:= Name
(Parent
(N
));
3286 -- Replace call with temporary and create its declaration
3289 Make_Defining_Identifier
(Loc
, New_Internal_Name
('C'));
3290 Set_Is_Internal
(Temp
);
3292 -- For the unconstrained case. the generated temporary has the
3293 -- same constrained declaration as the result variable.
3294 -- It may eventually be possible to remove that temporary and
3295 -- use the result variable directly.
3299 Make_Object_Declaration
(Loc
,
3300 Defining_Identifier
=> Temp
,
3301 Object_Definition
=>
3302 New_Copy_Tree
(Object_Definition
(Parent
(Targ1
))));
3304 Replace_Formals
(Decl
);
3308 Make_Object_Declaration
(Loc
,
3309 Defining_Identifier
=> Temp
,
3310 Object_Definition
=>
3311 New_Occurrence_Of
(Ret_Type
, Loc
));
3313 Set_Etype
(Temp
, Ret_Type
);
3316 Set_No_Initialization
(Decl
);
3317 Append
(Decl
, Decls
);
3318 Rewrite
(N
, New_Occurrence_Of
(Temp
, Loc
));
3323 Insert_Actions
(N
, Decls
);
3325 -- Traverse the tree and replace formals with actuals or their thunks.
3326 -- Attach block to tree before analysis and rewriting.
3328 Replace_Formals
(Blk
);
3329 Set_Parent
(Blk
, N
);
3331 if not Comes_From_Source
(Subp
)
3337 if Present
(Exit_Lab
) then
3339 -- If the body was a single expression, the single return statement
3340 -- and the corresponding label are useless.
3344 Nkind
(Last
(Statements
(Handled_Statement_Sequence
(Blk
)))) =
3347 Remove
(Last
(Statements
(Handled_Statement_Sequence
(Blk
))));
3349 Append
(Lab_Decl
, (Declarations
(Blk
)));
3350 Append
(Exit_Lab
, Statements
(Handled_Statement_Sequence
(Blk
)));
3354 -- Analyze Blk with In_Inlined_Body set, to avoid spurious errors on
3355 -- conflicting private views that Gigi would ignore. If this is
3356 -- predefined unit, analyze with checks off, as is done in the non-
3357 -- inlined run-time units.
3360 I_Flag
: constant Boolean := In_Inlined_Body
;
3363 In_Inlined_Body
:= True;
3367 Style
: constant Boolean := Style_Check
;
3369 Style_Check
:= False;
3370 Analyze
(Blk
, Suppress
=> All_Checks
);
3371 Style_Check
:= Style
;
3378 In_Inlined_Body
:= I_Flag
;
3381 if Ekind
(Subp
) = E_Procedure
then
3382 Rewrite_Procedure_Call
(N
, Blk
);
3384 Rewrite_Function_Call
(N
, Blk
);
3386 -- For the unconstrained case, the replacement of the call has been
3387 -- made prior to the complete analysis of the generated declarations.
3388 -- Propagate the proper type now.
3391 if Nkind
(N
) = N_Identifier
then
3392 Set_Etype
(N
, Etype
(Entity
(N
)));
3394 Set_Etype
(N
, Etype
(Targ1
));
3401 -- Cleanup mapping between formals and actuals for other expansions
3403 F
:= First_Formal
(Subp
);
3404 while Present
(F
) loop
3405 Set_Renamed_Object
(F
, Empty
);
3408 end Expand_Inlined_Call
;
3410 ----------------------------
3411 -- Expand_N_Function_Call --
3412 ----------------------------
3414 procedure Expand_N_Function_Call
(N
: Node_Id
) is
3415 Typ
: constant Entity_Id
:= Etype
(N
);
3417 function Returned_By_Reference
return Boolean;
3418 -- If the return type is returned through the secondary stack; that is
3419 -- by reference, we don't want to create a temp to force stack checking.
3420 -- ???"sec stack" is not right -- Ada 95 return-by-reference object are
3421 -- returned whereever they are.
3422 -- Shouldn't this function be moved to exp_util???
3424 function Rhs_Of_Assign_Or_Decl
(N
: Node_Id
) return Boolean;
3425 -- If the call is the right side of an assignment or the expression in
3426 -- an object declaration, we don't need to create a temp as the left
3427 -- side will already trigger stack checking if necessary.
3429 -- If the call is a component in an extension aggregate, it will be
3430 -- expanded into assignments as well, so no temporary is needed. This
3431 -- also solves the problem of functions returning types with unknown
3432 -- discriminants, where it is not possible to declare an object of the
3435 ---------------------------
3436 -- Returned_By_Reference --
3437 ---------------------------
3439 function Returned_By_Reference
return Boolean is
3443 if Is_Inherently_Limited_Type
(Typ
) then
3446 elsif Nkind
(Parent
(N
)) /= N_Return_Statement
then
3449 elsif Requires_Transient_Scope
(Typ
) then
3451 -- Verify that the return type of the enclosing function has the
3452 -- same constrained status as that of the expression.
3455 while Ekind
(S
) /= E_Function
loop
3459 return Is_Constrained
(Typ
) = Is_Constrained
(Etype
(S
));
3463 end Returned_By_Reference
;
3465 ---------------------------
3466 -- Rhs_Of_Assign_Or_Decl --
3467 ---------------------------
3469 function Rhs_Of_Assign_Or_Decl
(N
: Node_Id
) return Boolean is
3471 if (Nkind
(Parent
(N
)) = N_Assignment_Statement
3472 and then Expression
(Parent
(N
)) = N
)
3474 (Nkind
(Parent
(N
)) = N_Qualified_Expression
3475 and then Nkind
(Parent
(Parent
(N
))) = N_Assignment_Statement
3476 and then Expression
(Parent
(Parent
(N
))) = Parent
(N
))
3478 (Nkind
(Parent
(N
)) = N_Object_Declaration
3479 and then Expression
(Parent
(N
)) = N
)
3481 (Nkind
(Parent
(N
)) = N_Component_Association
3482 and then Expression
(Parent
(N
)) = N
3483 and then Nkind
(Parent
(Parent
(N
))) = N_Aggregate
3484 and then Rhs_Of_Assign_Or_Decl
(Parent
(Parent
(N
))))
3486 (Nkind
(Parent
(N
)) = N_Extension_Aggregate
3487 and then Is_Private_Type
(Etype
(Typ
)))
3493 end Rhs_Of_Assign_Or_Decl
;
3495 -- Start of processing for Expand_N_Function_Call
3498 -- A special check. If stack checking is enabled, and the return type
3499 -- might generate a large temporary, and the call is not the right side
3500 -- of an assignment, then generate an explicit temporary. We do this
3501 -- because otherwise gigi may generate a large temporary on the fly and
3502 -- this can cause trouble with stack checking.
3504 -- This is unecessary if the call is the expression in an object
3505 -- declaration, or if it appears outside of any library unit. This can
3506 -- only happen if it appears as an actual in a library-level instance,
3507 -- in which case a temporary will be generated for it once the instance
3508 -- itself is installed.
3510 if May_Generate_Large_Temp
(Typ
)
3511 and then not Rhs_Of_Assign_Or_Decl
(N
)
3512 and then not Returned_By_Reference
3513 and then Current_Scope
/= Standard_Standard
3515 if Stack_Checking_Enabled
then
3517 -- Note: it might be thought that it would be OK to use a call to
3518 -- Force_Evaluation here, but that's not good enough, because
3519 -- that can results in a 'Reference construct that may still need
3523 Loc
: constant Source_Ptr
:= Sloc
(N
);
3524 Temp_Obj
: constant Entity_Id
:=
3525 Make_Defining_Identifier
(Loc
,
3526 Chars
=> New_Internal_Name
('F'));
3527 Temp_Typ
: Entity_Id
:= Typ
;
3534 if Is_Tagged_Type
(Typ
)
3535 and then Present
(Controlling_Argument
(N
))
3537 if Nkind
(Parent
(N
)) /= N_Procedure_Call_Statement
3538 and then Nkind
(Parent
(N
)) /= N_Function_Call
3540 -- If this is a tag-indeterminate call, the object must
3543 if Is_Tag_Indeterminate
(N
) then
3544 Temp_Typ
:= Class_Wide_Type
(Typ
);
3548 -- If this is a dispatching call that is itself the
3549 -- controlling argument of an enclosing call, the
3550 -- nominal subtype of the object that replaces it must
3551 -- be classwide, so that dispatching will take place
3552 -- properly. If it is not a controlling argument, the
3553 -- object is not classwide.
3555 Proc
:= Entity
(Name
(Parent
(N
)));
3557 F
:= First_Formal
(Proc
);
3558 A
:= First_Actual
(Parent
(N
));
3564 if Is_Controlling_Formal
(F
) then
3565 Temp_Typ
:= Class_Wide_Type
(Typ
);
3571 Make_Object_Declaration
(Loc
,
3572 Defining_Identifier
=> Temp_Obj
,
3573 Object_Definition
=> New_Occurrence_Of
(Temp_Typ
, Loc
),
3574 Constant_Present
=> True,
3575 Expression
=> Relocate_Node
(N
));
3576 Set_Assignment_OK
(Decl
);
3578 Insert_Actions
(N
, New_List
(Decl
));
3579 Rewrite
(N
, New_Occurrence_Of
(Temp_Obj
, Loc
));
3583 -- If stack-checking is not enabled, increment serial number
3584 -- for internal names, so that subsequent symbols are consistent
3585 -- with and without stack-checking.
3587 Synchronize_Serial_Number
;
3589 -- Now we can expand the call with consistent symbol names
3594 -- Normal case, expand the call
3599 end Expand_N_Function_Call
;
3601 ---------------------------------------
3602 -- Expand_N_Procedure_Call_Statement --
3603 ---------------------------------------
3605 procedure Expand_N_Procedure_Call_Statement
(N
: Node_Id
) is
3608 end Expand_N_Procedure_Call_Statement
;
3610 ------------------------------
3611 -- Expand_N_Subprogram_Body --
3612 ------------------------------
3614 -- Add poll call if ATC polling is enabled, unless the body will be
3615 -- inlined by the back-end.
3617 -- Add return statement if last statement in body is not a return statement
3618 -- (this makes things easier on Gigi which does not want to have to handle
3619 -- a missing return).
3621 -- Add call to Activate_Tasks if body is a task activator
3623 -- Deal with possible detection of infinite recursion
3625 -- Eliminate body completely if convention stubbed
3627 -- Encode entity names within body, since we will not need to reference
3628 -- these entities any longer in the front end.
3630 -- Initialize scalar out parameters if Initialize/Normalize_Scalars
3632 -- Reset Pure indication if any parameter has root type System.Address
3636 procedure Expand_N_Subprogram_Body
(N
: Node_Id
) is
3637 Loc
: constant Source_Ptr
:= Sloc
(N
);
3638 H
: constant Node_Id
:= Handled_Statement_Sequence
(N
);
3639 Body_Id
: Entity_Id
;
3640 Spec_Id
: Entity_Id
;
3647 procedure Add_Return
(S
: List_Id
);
3648 -- Append a return statement to the statement sequence S if the last
3649 -- statement is not already a return or a goto statement. Note that
3650 -- the latter test is not critical, it does not matter if we add a
3651 -- few extra returns, since they get eliminated anyway later on.
3653 procedure Expand_Thread_Body
;
3654 -- Perform required expansion of a thread body
3660 procedure Add_Return
(S
: List_Id
) is
3662 if not Is_Transfer
(Last
(S
)) then
3664 -- The source location for the return is the end label
3665 -- of the procedure in all cases. This is a bit odd when
3666 -- there are exception handlers, but not much else we can do.
3668 Append_To
(S
, Make_Return_Statement
(Sloc
(End_Label
(H
))));
3672 ------------------------
3673 -- Expand_Thread_Body --
3674 ------------------------
3676 -- The required expansion of a thread body is as follows
3678 -- procedure <thread body procedure name> is
3680 -- _Secondary_Stack : aliased
3681 -- Storage_Elements.Storage_Array
3682 -- (1 .. Storage_Offset (Sec_Stack_Size));
3683 -- for _Secondary_Stack'Alignment use Standard'Maximum_Alignment;
3685 -- _Process_ATSD : aliased System.Threads.ATSD;
3688 -- System.Threads.Thread_Body_Enter;
3689 -- (_Secondary_Stack'Address,
3690 -- _Secondary_Stack'Length,
3691 -- _Process_ATSD'Address);
3694 -- <user declarations>
3696 -- <user statements>
3697 -- <user exception handlers>
3700 -- System.Threads.Thread_Body_Leave;
3703 -- when E : others =>
3704 -- System.Threads.Thread_Body_Exceptional_Exit (E);
3707 -- Note the exception handler is omitted if pragma Restriction
3708 -- No_Exception_Handlers is currently active.
3710 procedure Expand_Thread_Body
is
3711 User_Decls
: constant List_Id
:= Declarations
(N
);
3712 Sec_Stack_Len
: Node_Id
;
3714 TB_Pragma
: constant Node_Id
:=
3715 Get_Rep_Pragma
(Spec_Id
, Name_Thread_Body
);
3718 Ent_ATSD
: Entity_Id
;
3722 Decl_ATSD
: Node_Id
;
3724 Excep_Handlers
: List_Id
;
3727 New_Scope
(Spec_Id
);
3729 -- Get proper setting for secondary stack size
3731 if List_Length
(Pragma_Argument_Associations
(TB_Pragma
)) = 2 then
3733 Expression
(Last
(Pragma_Argument_Associations
(TB_Pragma
)));
3736 New_Occurrence_Of
(RTE
(RE_Default_Secondary_Stack_Size
), Loc
);
3739 Sec_Stack_Len
:= Convert_To
(RTE
(RE_Storage_Offset
), Sec_Stack_Len
);
3741 -- Build and set declarations for the wrapped thread body
3744 Make_Defining_Identifier
(Loc
,
3745 Chars
=> Name_uSecondary_Stack
);
3747 Make_Defining_Identifier
(Loc
,
3748 Chars
=> Name_uProcess_ATSD
);
3751 Make_Object_Declaration
(Loc
,
3752 Defining_Identifier
=> Ent_SS
,
3753 Aliased_Present
=> True,
3754 Object_Definition
=>
3755 Make_Subtype_Indication
(Loc
,
3757 New_Occurrence_Of
(RTE
(RE_Storage_Array
), Loc
),
3759 Make_Index_Or_Discriminant_Constraint
(Loc
,
3760 Constraints
=> New_List
(
3762 Low_Bound
=> Make_Integer_Literal
(Loc
, 1),
3763 High_Bound
=> Sec_Stack_Len
)))));
3766 Make_Object_Declaration
(Loc
,
3767 Defining_Identifier
=> Ent_ATSD
,
3768 Aliased_Present
=> True,
3769 Object_Definition
=> New_Occurrence_Of
(RTE
(RE_ATSD
), Loc
));
3771 Set_Declarations
(N
, New_List
(Decl_SS
, Decl_ATSD
));
3773 Analyze
(Decl_ATSD
);
3774 Set_Alignment
(Ent_SS
, UI_From_Int
(Maximum_Alignment
));
3776 -- Create new exception handler
3778 if Restriction_Active
(No_Exception_Handlers
) then
3779 Excep_Handlers
:= No_List
;
3782 Check_Restriction
(No_Exception_Handlers
, N
);
3785 Make_Defining_Identifier
(Loc
,
3788 Excep_Handlers
:= New_List
(
3789 Make_Exception_Handler
(Loc
,
3790 Choice_Parameter
=> Ent_EO
,
3791 Exception_Choices
=> New_List
(
3792 Make_Others_Choice
(Loc
)),
3793 Statements
=> New_List
(
3794 Make_Procedure_Call_Statement
(Loc
,
3797 (RTE
(RE_Thread_Body_Exceptional_Exit
), Loc
),
3798 Parameter_Associations
=> New_List
(
3799 New_Occurrence_Of
(Ent_EO
, Loc
))))));
3802 -- Now build new handled statement sequence and analyze it
3804 Set_Handled_Statement_Sequence
(N
,
3805 Make_Handled_Sequence_Of_Statements
(Loc
,
3806 Statements
=> New_List
(
3808 Make_Procedure_Call_Statement
(Loc
,
3809 Name
=> New_Occurrence_Of
(RTE
(RE_Thread_Body_Enter
), Loc
),
3810 Parameter_Associations
=> New_List
(
3812 Make_Attribute_Reference
(Loc
,
3813 Prefix
=> New_Occurrence_Of
(Ent_SS
, Loc
),
3814 Attribute_Name
=> Name_Address
),
3816 Make_Attribute_Reference
(Loc
,
3817 Prefix
=> New_Occurrence_Of
(Ent_SS
, Loc
),
3818 Attribute_Name
=> Name_Length
),
3820 Make_Attribute_Reference
(Loc
,
3821 Prefix
=> New_Occurrence_Of
(Ent_ATSD
, Loc
),
3822 Attribute_Name
=> Name_Address
))),
3824 Make_Block_Statement
(Loc
,
3825 Declarations
=> User_Decls
,
3826 Handled_Statement_Sequence
=> H
),
3828 Make_Procedure_Call_Statement
(Loc
,
3829 Name
=> New_Occurrence_Of
(RTE
(RE_Thread_Body_Leave
), Loc
))),
3831 Exception_Handlers
=> Excep_Handlers
));
3833 Analyze
(Handled_Statement_Sequence
(N
));
3835 end Expand_Thread_Body
;
3837 -- Start of processing for Expand_N_Subprogram_Body
3840 -- Set L to either the list of declarations if present, or
3841 -- to the list of statements if no declarations are present.
3842 -- This is used to insert new stuff at the start.
3844 if Is_Non_Empty_List
(Declarations
(N
)) then
3845 L
:= Declarations
(N
);
3847 L
:= Statements
(Handled_Statement_Sequence
(N
));
3850 -- Find entity for subprogram
3852 Body_Id
:= Defining_Entity
(N
);
3854 if Present
(Corresponding_Spec
(N
)) then
3855 Spec_Id
:= Corresponding_Spec
(N
);
3860 -- Need poll on entry to subprogram if polling enabled. We only
3861 -- do this for non-empty subprograms, since it does not seem
3862 -- necessary to poll for a dummy null subprogram. Do not add polling
3863 -- point if calls to this subprogram will be inlined by the back-end,
3864 -- to avoid repeated polling points in nested inlinings.
3866 if Is_Non_Empty_List
(L
) then
3867 if Is_Inlined
(Spec_Id
)
3868 and then Front_End_Inlining
3869 and then Optimization_Level
> 1
3873 Generate_Poll_Call
(First
(L
));
3877 -- If this is a Pure function which has any parameters whose root
3878 -- type is System.Address, reset the Pure indication, since it will
3879 -- likely cause incorrect code to be generated as the parameter is
3880 -- probably a pointer, and the fact that the same pointer is passed
3881 -- does not mean that the same value is being referenced.
3883 -- Note that if the programmer gave an explicit Pure_Function pragma,
3884 -- then we believe the programmer, and leave the subprogram Pure.
3886 -- This code should probably be at the freeze point, so that it
3887 -- happens even on a -gnatc (or more importantly -gnatt) compile
3888 -- so that the semantic tree has Is_Pure set properly ???
3890 if Is_Pure
(Spec_Id
)
3891 and then Is_Subprogram
(Spec_Id
)
3892 and then not Has_Pragma_Pure_Function
(Spec_Id
)
3898 F
:= First_Formal
(Spec_Id
);
3899 while Present
(F
) loop
3900 if Is_Descendent_Of_Address
(Etype
(F
)) then
3901 Set_Is_Pure
(Spec_Id
, False);
3903 if Spec_Id
/= Body_Id
then
3904 Set_Is_Pure
(Body_Id
, False);
3915 -- Initialize any scalar OUT args if Initialize/Normalize_Scalars
3917 if Init_Or_Norm_Scalars
and then Is_Subprogram
(Spec_Id
) then
3922 -- Loop through formals
3924 F
:= First_Formal
(Spec_Id
);
3925 while Present
(F
) loop
3926 if Is_Scalar_Type
(Etype
(F
))
3927 and then Ekind
(F
) = E_Out_Parameter
3929 -- Insert the initialization. We turn off validity checks
3930 -- for this assignment, since we do not want any check on
3931 -- the initial value itself (which may well be invalid).
3933 Insert_Before_And_Analyze
(First
(L
),
3934 Make_Assignment_Statement
(Loc
,
3935 Name
=> New_Occurrence_Of
(F
, Loc
),
3936 Expression
=> Get_Simple_Init_Val
(Etype
(F
), Loc
)),
3937 Suppress
=> Validity_Check
);
3945 Scop
:= Scope
(Spec_Id
);
3947 -- Add discriminal renamings to protected subprograms. Install new
3948 -- discriminals for expansion of the next subprogram of this protected
3951 if Is_List_Member
(N
)
3952 and then Present
(Parent
(List_Containing
(N
)))
3953 and then Nkind
(Parent
(List_Containing
(N
))) = N_Protected_Body
3955 Add_Discriminal_Declarations
3956 (Declarations
(N
), Scop
, Name_uObject
, Loc
);
3957 Add_Private_Declarations
(Declarations
(N
), Scop
, Name_uObject
, Loc
);
3959 -- Associate privals and discriminals with the next protected
3960 -- operation body to be expanded. These are used to expand references
3961 -- to private data objects and discriminants, respectively.
3963 Next_Op
:= Next_Protected_Operation
(N
);
3965 if Present
(Next_Op
) then
3966 Dec
:= Parent
(Base_Type
(Scop
));
3967 Set_Privals
(Dec
, Next_Op
, Loc
);
3968 Set_Discriminals
(Dec
);
3972 -- Clear out statement list for stubbed procedure
3974 if Present
(Corresponding_Spec
(N
)) then
3975 Set_Elaboration_Flag
(N
, Spec_Id
);
3977 if Convention
(Spec_Id
) = Convention_Stubbed
3978 or else Is_Eliminated
(Spec_Id
)
3980 Set_Declarations
(N
, Empty_List
);
3981 Set_Handled_Statement_Sequence
(N
,
3982 Make_Handled_Sequence_Of_Statements
(Loc
,
3983 Statements
=> New_List
(
3984 Make_Null_Statement
(Loc
))));
3989 -- Returns_By_Ref flag is normally set when the subprogram is frozen
3990 -- but subprograms with no specs are not frozen.
3993 Typ
: constant Entity_Id
:= Etype
(Spec_Id
);
3994 Utyp
: constant Entity_Id
:= Underlying_Type
(Typ
);
3997 if not Acts_As_Spec
(N
)
3998 and then Nkind
(Parent
(Parent
(Spec_Id
))) /=
3999 N_Subprogram_Body_Stub
4003 elsif Is_Inherently_Limited_Type
(Typ
) then
4004 Set_Returns_By_Ref
(Spec_Id
);
4006 elsif Present
(Utyp
)
4007 and then (Is_Class_Wide_Type
(Utyp
) or else Controlled_Type
(Utyp
))
4009 Set_Returns_By_Ref
(Spec_Id
);
4013 -- For a procedure, we add a return for all possible syntactic ends
4014 -- of the subprogram. Note that reanalysis is not necessary in this
4015 -- case since it would require a lot of work and accomplish nothing.
4017 if Ekind
(Spec_Id
) = E_Procedure
4018 or else Ekind
(Spec_Id
) = E_Generic_Procedure
4020 Add_Return
(Statements
(H
));
4022 if Present
(Exception_Handlers
(H
)) then
4023 Except_H
:= First_Non_Pragma
(Exception_Handlers
(H
));
4024 while Present
(Except_H
) loop
4025 Add_Return
(Statements
(Except_H
));
4026 Next_Non_Pragma
(Except_H
);
4030 -- For a function, we must deal with the case where there is at least
4031 -- one missing return. What we do is to wrap the entire body of the
4032 -- function in a block:
4045 -- raise Program_Error;
4048 -- This approach is necessary because the raise must be signalled
4049 -- to the caller, not handled by any local handler (RM 6.4(11)).
4051 -- Note: we do not need to analyze the constructed sequence here,
4052 -- since it has no handler, and an attempt to analyze the handled
4053 -- statement sequence twice is risky in various ways (e.g. the
4054 -- issue of expanding cleanup actions twice).
4056 elsif Has_Missing_Return
(Spec_Id
) then
4058 Hloc
: constant Source_Ptr
:= Sloc
(H
);
4059 Blok
: constant Node_Id
:=
4060 Make_Block_Statement
(Hloc
,
4061 Handled_Statement_Sequence
=> H
);
4062 Rais
: constant Node_Id
:=
4063 Make_Raise_Program_Error
(Hloc
,
4064 Reason
=> PE_Missing_Return
);
4067 Set_Handled_Statement_Sequence
(N
,
4068 Make_Handled_Sequence_Of_Statements
(Hloc
,
4069 Statements
=> New_List
(Blok
, Rais
)));
4071 New_Scope
(Spec_Id
);
4078 -- If subprogram contains a parameterless recursive call, then we may
4079 -- have an infinite recursion, so see if we can generate code to check
4080 -- for this possibility if storage checks are not suppressed.
4082 if Ekind
(Spec_Id
) = E_Procedure
4083 and then Has_Recursive_Call
(Spec_Id
)
4084 and then not Storage_Checks_Suppressed
(Spec_Id
)
4086 Detect_Infinite_Recursion
(N
, Spec_Id
);
4089 -- Finally, if we are in Normalize_Scalars mode, then any scalar out
4090 -- parameters must be initialized to the appropriate default value.
4092 if Ekind
(Spec_Id
) = E_Procedure
and then Normalize_Scalars
then
4099 Formal
:= First_Formal
(Spec_Id
);
4100 while Present
(Formal
) loop
4101 Floc
:= Sloc
(Formal
);
4103 if Ekind
(Formal
) = E_Out_Parameter
4104 and then Is_Scalar_Type
(Etype
(Formal
))
4107 Make_Assignment_Statement
(Floc
,
4108 Name
=> New_Occurrence_Of
(Formal
, Floc
),
4110 Get_Simple_Init_Val
(Etype
(Formal
), Floc
));
4111 Prepend
(Stm
, Declarations
(N
));
4115 Next_Formal
(Formal
);
4120 -- Deal with thread body
4122 if Is_Thread_Body
(Spec_Id
) then
4126 -- Set to encode entity names in package body before gigi is called
4128 Qualify_Entity_Names
(N
);
4129 end Expand_N_Subprogram_Body
;
4131 -----------------------------------
4132 -- Expand_N_Subprogram_Body_Stub --
4133 -----------------------------------
4135 procedure Expand_N_Subprogram_Body_Stub
(N
: Node_Id
) is
4137 if Present
(Corresponding_Body
(N
)) then
4138 Expand_N_Subprogram_Body
(
4139 Unit_Declaration_Node
(Corresponding_Body
(N
)));
4141 end Expand_N_Subprogram_Body_Stub
;
4143 -------------------------------------
4144 -- Expand_N_Subprogram_Declaration --
4145 -------------------------------------
4147 -- If the declaration appears within a protected body, it is a private
4148 -- operation of the protected type. We must create the corresponding
4149 -- protected subprogram an associated formals. For a normal protected
4150 -- operation, this is done when expanding the protected type declaration.
4152 -- If the declaration is for a null procedure, emit null body
4154 procedure Expand_N_Subprogram_Declaration
(N
: Node_Id
) is
4155 Loc
: constant Source_Ptr
:= Sloc
(N
);
4156 Subp
: constant Entity_Id
:= Defining_Entity
(N
);
4157 Scop
: constant Entity_Id
:= Scope
(Subp
);
4158 Prot_Decl
: Node_Id
;
4160 Prot_Id
: Entity_Id
;
4163 -- Deal with case of protected subprogram. Do not generate protected
4164 -- operation if operation is flagged as eliminated.
4166 if Is_List_Member
(N
)
4167 and then Present
(Parent
(List_Containing
(N
)))
4168 and then Nkind
(Parent
(List_Containing
(N
))) = N_Protected_Body
4169 and then Is_Protected_Type
(Scop
)
4171 if No
(Protected_Body_Subprogram
(Subp
))
4172 and then not Is_Eliminated
(Subp
)
4175 Make_Subprogram_Declaration
(Loc
,
4177 Build_Protected_Sub_Specification
4178 (N
, Scop
, Unprotected_Mode
));
4180 -- The protected subprogram is declared outside of the protected
4181 -- body. Given that the body has frozen all entities so far, we
4182 -- analyze the subprogram and perform freezing actions explicitly.
4183 -- If the body is a subunit, the insertion point is before the
4184 -- stub in the parent.
4186 Prot_Bod
:= Parent
(List_Containing
(N
));
4188 if Nkind
(Parent
(Prot_Bod
)) = N_Subunit
then
4189 Prot_Bod
:= Corresponding_Stub
(Parent
(Prot_Bod
));
4192 Insert_Before
(Prot_Bod
, Prot_Decl
);
4193 Prot_Id
:= Defining_Unit_Name
(Specification
(Prot_Decl
));
4195 New_Scope
(Scope
(Scop
));
4196 Analyze
(Prot_Decl
);
4197 Create_Extra_Formals
(Prot_Id
);
4198 Set_Protected_Body_Subprogram
(Subp
, Prot_Id
);
4202 -- Ada 2005 (AI-348): Generation of the null body
4204 elsif Nkind
(Specification
(N
)) = N_Procedure_Specification
4205 and then Null_Present
(Specification
(N
))
4208 Bod
: constant Node_Id
:=
4209 Make_Subprogram_Body
(Loc
,
4211 New_Copy_Tree
(Specification
(N
)),
4212 Declarations
=> New_List
,
4213 Handled_Statement_Sequence
=>
4214 Make_Handled_Sequence_Of_Statements
(Loc
,
4215 Statements
=> New_List
(Make_Null_Statement
(Loc
))));
4217 Set_Body_To_Inline
(N
, Bod
);
4218 Insert_After
(N
, Bod
);
4221 -- Corresponding_Spec isn't being set by Analyze_Subprogram_Body,
4222 -- evidently because Set_Has_Completion is called earlier for null
4223 -- procedures in Analyze_Subprogram_Declaration, so we force its
4224 -- setting here. If the setting of Has_Completion is not set
4225 -- earlier, then it can result in missing body errors if other
4226 -- errors were already reported (since expansion is turned off).
4228 -- Should creation of the empty body be moved to the analyzer???
4230 Set_Corresponding_Spec
(Bod
, Defining_Entity
(Specification
(N
)));
4233 end Expand_N_Subprogram_Declaration
;
4235 ---------------------------------------
4236 -- Expand_Protected_Object_Reference --
4237 ---------------------------------------
4239 function Expand_Protected_Object_Reference
4241 Scop
: Entity_Id
) return Node_Id
4243 Loc
: constant Source_Ptr
:= Sloc
(N
);
4251 Make_Identifier
(Loc
,
4252 Chars
=> Name_uObject
);
4253 Set_Etype
(Rec
, Corresponding_Record_Type
(Scop
));
4255 -- Find enclosing protected operation, and retrieve its first parameter,
4256 -- which denotes the enclosing protected object. If the enclosing
4257 -- operation is an entry, we are immediately within the protected body,
4258 -- and we can retrieve the object from the service entries procedure. A
4259 -- barrier function has has the same signature as an entry. A barrier
4260 -- function is compiled within the protected object, but unlike
4261 -- protected operations its never needs locks, so that its protected
4262 -- body subprogram points to itself.
4264 Proc
:= Current_Scope
;
4265 while Present
(Proc
)
4266 and then Scope
(Proc
) /= Scop
4268 Proc
:= Scope
(Proc
);
4271 Corr
:= Protected_Body_Subprogram
(Proc
);
4275 -- Previous error left expansion incomplete.
4276 -- Nothing to do on this call.
4283 (First
(Parameter_Specifications
(Parent
(Corr
))));
4285 if Is_Subprogram
(Proc
)
4286 and then Proc
/= Corr
4288 -- Protected function or procedure
4290 Set_Entity
(Rec
, Param
);
4292 -- Rec is a reference to an entity which will not be in scope when
4293 -- the call is reanalyzed, and needs no further analysis.
4298 -- Entry or barrier function for entry body. The first parameter of
4299 -- the entry body procedure is pointer to the object. We create a
4300 -- local variable of the proper type, duplicating what is done to
4301 -- define _object later on.
4305 Obj_Ptr
: constant Entity_Id
:= Make_Defining_Identifier
(Loc
,
4307 New_Internal_Name
('T'));
4311 Make_Full_Type_Declaration
(Loc
,
4312 Defining_Identifier
=> Obj_Ptr
,
4314 Make_Access_To_Object_Definition
(Loc
,
4315 Subtype_Indication
=>
4317 (Corresponding_Record_Type
(Scop
), Loc
))));
4319 Insert_Actions
(N
, Decls
);
4320 Insert_Actions
(N
, Freeze_Entity
(Obj_Ptr
, Sloc
(N
)));
4323 Make_Explicit_Dereference
(Loc
,
4324 Unchecked_Convert_To
(Obj_Ptr
,
4325 New_Occurrence_Of
(Param
, Loc
)));
4327 -- Analyze new actual. Other actuals in calls are already analyzed
4328 -- and the list of actuals is not renalyzed after rewriting.
4330 Set_Parent
(Rec
, N
);
4336 end Expand_Protected_Object_Reference
;
4338 --------------------------------------
4339 -- Expand_Protected_Subprogram_Call --
4340 --------------------------------------
4342 procedure Expand_Protected_Subprogram_Call
4350 -- If the protected object is not an enclosing scope, this is
4351 -- an inter-object function call. Inter-object procedure
4352 -- calls are expanded by Exp_Ch9.Build_Simple_Entry_Call.
4353 -- The call is intra-object only if the subprogram being
4354 -- called is in the protected body being compiled, and if the
4355 -- protected object in the call is statically the enclosing type.
4356 -- The object may be an component of some other data structure,
4357 -- in which case this must be handled as an inter-object call.
4359 if not In_Open_Scopes
(Scop
)
4360 or else not Is_Entity_Name
(Name
(N
))
4362 if Nkind
(Name
(N
)) = N_Selected_Component
then
4363 Rec
:= Prefix
(Name
(N
));
4366 pragma Assert
(Nkind
(Name
(N
)) = N_Indexed_Component
);
4367 Rec
:= Prefix
(Prefix
(Name
(N
)));
4370 Build_Protected_Subprogram_Call
(N
,
4371 Name
=> New_Occurrence_Of
(Subp
, Sloc
(N
)),
4372 Rec
=> Convert_Concurrent
(Rec
, Etype
(Rec
)),
4376 Rec
:= Expand_Protected_Object_Reference
(N
, Scop
);
4382 Build_Protected_Subprogram_Call
(N
,
4391 -- If it is a function call it can appear in elaboration code and
4392 -- the called entity must be frozen here.
4394 if Ekind
(Subp
) = E_Function
then
4395 Freeze_Expression
(Name
(N
));
4397 end Expand_Protected_Subprogram_Call
;
4399 --------------------------------
4400 -- Is_Build_In_Place_Function --
4401 --------------------------------
4403 function Is_Build_In_Place_Function
(E
: Entity_Id
) return Boolean is
4405 -- For now we test whether E denotes a function or access-to-function
4406 -- type whose result subtype is constrained and inherently limited.
4407 -- Later this test will be revised to include unconstrained limited
4408 -- types and composite nonlimited types in general. Functions with
4409 -- a foreign convention or whose result type has a foreign convention
4412 if Ekind
(E
) = E_Function
4413 or else (Ekind
(E
) = E_Subprogram_Type
4414 and then Etype
(E
) /= Standard_Void_Type
)
4416 if Has_Foreign_Convention
(E
)
4417 or else Has_Foreign_Convention
(Etype
(E
))
4422 return Is_Inherently_Limited_Type
(Etype
(E
))
4423 and then Is_Constrained
(Etype
(E
));
4429 end Is_Build_In_Place_Function
;
4431 -------------------------------------
4432 -- Is_Build_In_Place_Function_Call --
4433 -------------------------------------
4435 function Is_Build_In_Place_Function_Call
(N
: Node_Id
) return Boolean is
4436 Exp_Node
: Node_Id
:= N
;
4437 Function_Id
: Entity_Id
;
4440 if Nkind
(Exp_Node
) = N_Qualified_Expression
then
4441 Exp_Node
:= Expression
(N
);
4444 if Nkind
(Exp_Node
) /= N_Function_Call
then
4448 if Is_Entity_Name
(Name
(Exp_Node
)) then
4449 Function_Id
:= Entity
(Name
(Exp_Node
));
4451 elsif Nkind
(Name
(Exp_Node
)) = N_Explicit_Dereference
then
4452 Function_Id
:= Etype
(Name
(Exp_Node
));
4455 return Is_Build_In_Place_Function
(Function_Id
);
4457 end Is_Build_In_Place_Function_Call
;
4459 -----------------------
4460 -- Freeze_Subprogram --
4461 -----------------------
4463 procedure Freeze_Subprogram
(N
: Node_Id
) is
4464 Loc
: constant Source_Ptr
:= Sloc
(N
);
4465 E
: constant Entity_Id
:= Entity
(N
);
4467 procedure Register_Predefined_DT_Entry
(Prim
: Entity_Id
);
4468 -- (Ada 2005): Register a predefined primitive in all the secondary
4469 -- dispatch tables of its primitive type.
4471 ----------------------------------
4472 -- Register_Predefined_DT_Entry --
4473 ----------------------------------
4475 procedure Register_Predefined_DT_Entry
(Prim
: Entity_Id
) is
4476 Iface_DT_Ptr
: Elmt_Id
;
4477 Iface_Typ
: Entity_Id
;
4478 Iface_Elmt
: Elmt_Id
;
4479 Tagged_Typ
: Entity_Id
;
4480 Thunk_Id
: Entity_Id
;
4483 Tagged_Typ
:= Find_Dispatching_Type
(Prim
);
4485 if No
(Access_Disp_Table
(Tagged_Typ
))
4486 or else No
(Abstract_Interfaces
(Tagged_Typ
))
4487 or else not RTE_Available
(RE_Interface_Tag
)
4492 -- Skip the first access-to-dispatch-table pointer since it leads
4493 -- to the primary dispatch table. We are only concerned with the
4494 -- secondary dispatch table pointers. Note that the access-to-
4495 -- dispatch-table pointer corresponds to the first implemented
4496 -- interface retrieved below.
4499 Next_Elmt
(First_Elmt
(Access_Disp_Table
(Tagged_Typ
)));
4500 Iface_Elmt
:= First_Elmt
(Abstract_Interfaces
(Tagged_Typ
));
4501 while Present
(Iface_DT_Ptr
) and then Present
(Iface_Elmt
) loop
4502 Iface_Typ
:= Node
(Iface_Elmt
);
4504 if not Is_Ancestor
(Iface_Typ
, Tagged_Typ
) then
4506 Make_Defining_Identifier
(Loc
,
4507 Chars
=> New_Internal_Name
('T'));
4509 Insert_Actions
(N
, New_List
(
4510 Expand_Interface_Thunk
4512 Thunk_Alias
=> Prim
,
4513 Thunk_Id
=> Thunk_Id
),
4515 Make_DT_Access_Action
(Iface_Typ
,
4516 Action
=> Set_Predefined_Prim_Op_Address
,
4518 Unchecked_Convert_To
(RTE
(RE_Tag
),
4519 New_Reference_To
(Node
(Iface_DT_Ptr
), Loc
)),
4521 Make_Integer_Literal
(Loc
, DT_Position
(Prim
)),
4523 Make_Attribute_Reference
(Loc
,
4524 Prefix
=> New_Reference_To
(Thunk_Id
, Loc
),
4525 Attribute_Name
=> Name_Address
)))));
4528 Next_Elmt
(Iface_DT_Ptr
);
4529 Next_Elmt
(Iface_Elmt
);
4531 end Register_Predefined_DT_Entry
;
4533 -- Start of processing for Freeze_Subprogram
4536 -- We assume that imported CPP primitives correspond with objects
4537 -- whose constructor is in the CPP side (and therefore we don't need
4538 -- to generate code to register them in the dispatch table).
4540 if not Debug_Flag_QQ
4541 and then Is_Imported
(E
)
4542 and then Convention
(E
) = Convention_CPP
4547 -- When a primitive is frozen, enter its name in the corresponding
4548 -- dispatch table. If the DTC_Entity field is not set this is an
4549 -- overridden primitive that can be ignored. We suppress the
4550 -- initialization of the dispatch table entry when Java_VM because
4551 -- the dispatching mechanism is handled internally by the JVM.
4553 if Is_Dispatching_Operation
(E
)
4554 and then not Is_Abstract
(E
)
4555 and then Present
(DTC_Entity
(E
))
4556 and then not Java_VM
4557 and then not Is_CPP_Class
(Scope
(DTC_Entity
(E
)))
4559 Check_Overriding_Operation
(E
);
4561 -- Ada 95 case: Register the subprogram in the primary dispatch table
4563 if Ada_Version
< Ada_05
then
4565 -- Do not register the subprogram in the dispatch table if we
4566 -- are compiling with the No_Dispatching_Calls restriction.
4568 if not Restriction_Active
(No_Dispatching_Calls
) then
4570 Fill_DT_Entry
(Sloc
(N
), Prim
=> E
));
4573 -- Ada 2005 case: Register the subprogram in the secondary dispatch
4574 -- tables associated with abstract interfaces.
4578 Typ
: constant Entity_Id
:= Scope
(DTC_Entity
(E
));
4581 -- There is no dispatch table associated with abstract
4582 -- interface types. Each type implementing interfaces will
4583 -- fill the associated secondary DT entries.
4585 if not Is_Interface
(Typ
)
4586 or else Present
(Alias
(E
))
4588 -- Ada 2005 (AI-251): Check if this entry corresponds with
4589 -- a subprogram that covers an abstract interface type.
4591 if Present
(Abstract_Interface_Alias
(E
)) then
4592 Register_Interface_DT_Entry
(N
, E
);
4594 -- Common case: Primitive subprogram
4597 -- Generate thunks for all the predefined operations
4599 if not Restriction_Active
(No_Dispatching_Calls
) then
4600 if Is_Predefined_Dispatching_Operation
(E
) then
4601 Register_Predefined_DT_Entry
(E
);
4605 Fill_DT_Entry
(Sloc
(N
), Prim
=> E
));
4613 -- Mark functions that return by reference. Note that it cannot be
4614 -- part of the normal semantic analysis of the spec since the
4615 -- underlying returned type may not be known yet (for private types).
4618 Typ
: constant Entity_Id
:= Etype
(E
);
4619 Utyp
: constant Entity_Id
:= Underlying_Type
(Typ
);
4622 if Is_Inherently_Limited_Type
(Typ
) then
4623 Set_Returns_By_Ref
(E
);
4625 elsif Present
(Utyp
)
4626 and then (Is_Class_Wide_Type
(Utyp
) or else Controlled_Type
(Utyp
))
4628 Set_Returns_By_Ref
(E
);
4631 end Freeze_Subprogram
;
4633 -------------------------------------------
4634 -- Make_Build_In_Place_Call_In_Allocator --
4635 -------------------------------------------
4637 procedure Make_Build_In_Place_Call_In_Allocator
4638 (Allocator
: Node_Id
;
4639 Function_Call
: Node_Id
)
4642 Func_Call
: Node_Id
:= Function_Call
;
4643 Function_Id
: Entity_Id
;
4644 Result_Subt
: Entity_Id
;
4645 Acc_Type
: constant Entity_Id
:= Etype
(Allocator
);
4646 New_Allocator
: Node_Id
;
4647 Return_Obj_Access
: Entity_Id
;
4650 if Nkind
(Func_Call
) = N_Qualified_Expression
then
4651 Func_Call
:= Expression
(Func_Call
);
4654 Loc
:= Sloc
(Function_Call
);
4656 if Is_Entity_Name
(Name
(Func_Call
)) then
4657 Function_Id
:= Entity
(Name
(Func_Call
));
4659 elsif Nkind
(Name
(Func_Call
)) = N_Explicit_Dereference
then
4660 Function_Id
:= Etype
(Name
(Func_Call
));
4663 raise Program_Error
;
4666 Result_Subt
:= Etype
(Function_Id
);
4668 -- Replace the initialized allocator of form "new T'(Func (...))" with
4669 -- an uninitialized allocator of form "new T", where T is the result
4670 -- subtype of the called function. The call to the function is handled
4671 -- separately further below.
4674 Make_Allocator
(Loc
, New_Reference_To
(Result_Subt
, Loc
));
4675 Set_No_Initialization
(New_Allocator
);
4677 Rewrite
(Allocator
, New_Allocator
);
4679 -- Create a new access object and initialize it to the result of the new
4680 -- uninitialized allocator.
4682 Return_Obj_Access
:=
4683 Make_Defining_Identifier
(Loc
, New_Internal_Name
('R'));
4684 Set_Etype
(Return_Obj_Access
, Acc_Type
);
4686 Insert_Action
(Allocator
,
4687 Make_Object_Declaration
(Loc
,
4688 Defining_Identifier
=> Return_Obj_Access
,
4689 Object_Definition
=> New_Reference_To
(Acc_Type
, Loc
),
4690 Expression
=> Relocate_Node
(Allocator
)));
4692 -- Add an implicit actual to the function call that provides access to
4693 -- the allocated object. An unchecked conversion to the (specific)
4694 -- result subtype of the function is inserted to handle the case where
4695 -- the access type of the allocator has a class-wide designated type.
4697 Add_Access_Actual_To_Build_In_Place_Call
4700 Make_Unchecked_Type_Conversion
(Loc
,
4701 Subtype_Mark
=> New_Reference_To
(Result_Subt
, Loc
),
4703 Make_Explicit_Dereference
(Loc
,
4704 Prefix
=> New_Reference_To
(Return_Obj_Access
, Loc
))));
4706 -- Finally, replace the allocator node with a reference to the result
4707 -- of the function call itself (which will effectively be an access
4708 -- to the object created by the allocator).
4710 Rewrite
(Allocator
, Make_Reference
(Loc
, Relocate_Node
(Function_Call
)));
4711 Analyze_And_Resolve
(Allocator
, Acc_Type
);
4712 end Make_Build_In_Place_Call_In_Allocator
;
4714 ---------------------------------------------------
4715 -- Make_Build_In_Place_Call_In_Anonymous_Context --
4716 ---------------------------------------------------
4718 procedure Make_Build_In_Place_Call_In_Anonymous_Context
4719 (Function_Call
: Node_Id
)
4722 Func_Call
: Node_Id
:= Function_Call
;
4723 Function_Id
: Entity_Id
;
4724 Result_Subt
: Entity_Id
;
4725 Return_Obj_Id
: Entity_Id
;
4726 Return_Obj_Decl
: Entity_Id
;
4729 if Nkind
(Func_Call
) = N_Qualified_Expression
then
4730 Func_Call
:= Expression
(Func_Call
);
4733 Loc
:= Sloc
(Function_Call
);
4735 if Is_Entity_Name
(Name
(Func_Call
)) then
4736 Function_Id
:= Entity
(Name
(Func_Call
));
4738 elsif Nkind
(Name
(Func_Call
)) = N_Explicit_Dereference
then
4739 Function_Id
:= Etype
(Name
(Func_Call
));
4742 raise Program_Error
;
4745 Result_Subt
:= Etype
(Function_Id
);
4747 -- Create a temporary object to hold the function result
4750 Make_Defining_Identifier
(Loc
,
4751 Chars
=> New_Internal_Name
('R'));
4752 Set_Etype
(Return_Obj_Id
, Result_Subt
);
4755 Make_Object_Declaration
(Loc
,
4756 Defining_Identifier
=> Return_Obj_Id
,
4757 Aliased_Present
=> True,
4758 Object_Definition
=> New_Reference_To
(Result_Subt
, Loc
));
4760 Set_No_Initialization
(Return_Obj_Decl
);
4762 Insert_Action
(Func_Call
, Return_Obj_Decl
);
4764 -- Add an implicit actual to the function call that provides access to
4765 -- the caller's return object.
4767 Add_Access_Actual_To_Build_In_Place_Call
4768 (Func_Call
, Function_Id
, New_Reference_To
(Return_Obj_Id
, Loc
));
4769 end Make_Build_In_Place_Call_In_Anonymous_Context
;
4771 ---------------------------------------------------
4772 -- Make_Build_In_Place_Call_In_Assignment --
4773 ---------------------------------------------------
4775 procedure Make_Build_In_Place_Call_In_Assignment
4777 Function_Call
: Node_Id
)
4779 Lhs
: constant Node_Id
:= Name
(Assign
);
4781 Func_Call
: Node_Id
:= Function_Call
;
4782 Function_Id
: Entity_Id
;
4783 Result_Subt
: Entity_Id
;
4784 Ref_Type
: Entity_Id
;
4785 Ptr_Typ_Decl
: Node_Id
;
4790 if Nkind
(Func_Call
) = N_Qualified_Expression
then
4791 Func_Call
:= Expression
(Func_Call
);
4794 Loc
:= Sloc
(Function_Call
);
4796 if Is_Entity_Name
(Name
(Func_Call
)) then
4797 Function_Id
:= Entity
(Name
(Func_Call
));
4799 elsif Nkind
(Name
(Func_Call
)) = N_Explicit_Dereference
then
4800 Function_Id
:= Etype
(Name
(Func_Call
));
4803 raise Program_Error
;
4806 Result_Subt
:= Etype
(Function_Id
);
4808 -- Add an implicit actual to the function call that provides access to
4809 -- the caller's return object.
4811 Add_Access_Actual_To_Build_In_Place_Call
4814 Make_Unchecked_Type_Conversion
(Loc
,
4815 Subtype_Mark
=> New_Reference_To
(Result_Subt
, Loc
),
4816 Expression
=> Relocate_Node
(Lhs
)));
4818 -- Create an access type designating the function's result subtype
4821 Make_Defining_Identifier
(Loc
, New_Internal_Name
('A'));
4824 Make_Full_Type_Declaration
(Loc
,
4825 Defining_Identifier
=> Ref_Type
,
4827 Make_Access_To_Object_Definition
(Loc
,
4828 All_Present
=> True,
4829 Subtype_Indication
=>
4830 New_Reference_To
(Result_Subt
, Loc
)));
4832 Insert_After_And_Analyze
(Assign
, Ptr_Typ_Decl
);
4834 -- Finally, create an access object initialized to a reference to the
4838 Make_Defining_Identifier
(Loc
,
4839 Chars
=> New_Internal_Name
('R'));
4840 Set_Etype
(Def_Id
, Ref_Type
);
4843 Make_Reference
(Loc
,
4844 Prefix
=> Relocate_Node
(Func_Call
));
4846 Insert_After_And_Analyze
(Ptr_Typ_Decl
,
4847 Make_Object_Declaration
(Loc
,
4848 Defining_Identifier
=> Def_Id
,
4849 Object_Definition
=> New_Reference_To
(Ref_Type
, Loc
),
4850 Expression
=> New_Expr
));
4852 Rewrite
(Assign
, Make_Null_Statement
(Loc
));
4853 end Make_Build_In_Place_Call_In_Assignment
;
4855 ----------------------------------------------------
4856 -- Make_Build_In_Place_Call_In_Object_Declaration --
4857 ----------------------------------------------------
4859 procedure Make_Build_In_Place_Call_In_Object_Declaration
4860 (Object_Decl
: Node_Id
;
4861 Function_Call
: Node_Id
)
4864 Func_Call
: Node_Id
:= Function_Call
;
4865 Function_Id
: Entity_Id
;
4866 Result_Subt
: Entity_Id
;
4867 Ref_Type
: Entity_Id
;
4868 Ptr_Typ_Decl
: Node_Id
;
4873 if Nkind
(Func_Call
) = N_Qualified_Expression
then
4874 Func_Call
:= Expression
(Func_Call
);
4877 Loc
:= Sloc
(Function_Call
);
4879 if Is_Entity_Name
(Name
(Func_Call
)) then
4880 Function_Id
:= Entity
(Name
(Func_Call
));
4882 elsif Nkind
(Name
(Func_Call
)) = N_Explicit_Dereference
then
4883 Function_Id
:= Etype
(Name
(Func_Call
));
4886 raise Program_Error
;
4889 Result_Subt
:= Etype
(Function_Id
);
4891 -- Add an implicit actual to the function call that provides access to
4892 -- the declared object. An unchecked conversion to the (specific) result
4893 -- type of the function is inserted to handle the case where the object
4894 -- is declared with a class-wide type.
4896 Add_Access_Actual_To_Build_In_Place_Call
4899 Make_Unchecked_Type_Conversion
(Loc
,
4900 Subtype_Mark
=> New_Reference_To
(Result_Subt
, Loc
),
4901 Expression
=> New_Reference_To
4902 (Defining_Identifier
(Object_Decl
), Loc
)));
4904 -- Create an access type designating the function's result subtype
4907 Make_Defining_Identifier
(Loc
, New_Internal_Name
('A'));
4910 Make_Full_Type_Declaration
(Loc
,
4911 Defining_Identifier
=> Ref_Type
,
4913 Make_Access_To_Object_Definition
(Loc
,
4914 All_Present
=> True,
4915 Subtype_Indication
=>
4916 New_Reference_To
(Result_Subt
, Loc
)));
4918 Insert_After_And_Analyze
(Object_Decl
, Ptr_Typ_Decl
);
4920 -- Finally, create an access object initialized to a reference to the
4924 Make_Defining_Identifier
(Loc
,
4925 Chars
=> New_Internal_Name
('R'));
4926 Set_Etype
(Def_Id
, Ref_Type
);
4929 Make_Reference
(Loc
,
4930 Prefix
=> Relocate_Node
(Func_Call
));
4932 Insert_After_And_Analyze
(Ptr_Typ_Decl
,
4933 Make_Object_Declaration
(Loc
,
4934 Defining_Identifier
=> Def_Id
,
4935 Object_Definition
=> New_Reference_To
(Ref_Type
, Loc
),
4936 Expression
=> New_Expr
));
4938 Set_Expression
(Object_Decl
, Empty
);
4939 Set_No_Initialization
(Object_Decl
);
4941 -- If the object entity has a class-wide Etype, then we need to change
4942 -- it to the result subtype of the function call, because otherwise the
4943 -- object will be class-wide without an explicit intialization and won't
4944 -- be allocated properly by the back end. It seems unclean to make such
4945 -- a revision to the type at this point, and we should try to improve
4946 -- this treatment when build-in-place functions with class-wide results
4947 -- are implemented. ???
4949 if Is_Class_Wide_Type
(Etype
(Defining_Identifier
(Object_Decl
))) then
4950 Set_Etype
(Defining_Identifier
(Object_Decl
), Result_Subt
);
4952 end Make_Build_In_Place_Call_In_Object_Declaration
;
4954 ---------------------------------
4955 -- Register_Interface_DT_Entry --
4956 ---------------------------------
4958 procedure Register_Interface_DT_Entry
4959 (Related_Nod
: Node_Id
;
4962 Loc
: constant Source_Ptr
:= Sloc
(Prim
);
4963 Iface_Typ
: Entity_Id
;
4964 Tagged_Typ
: Entity_Id
;
4965 Thunk_Id
: Entity_Id
;
4968 -- Nothing to do if the run-time does not support abstract interfaces
4970 if not (RTE_Available
(RE_Interface_Tag
)) then
4974 Tagged_Typ
:= Find_Dispatching_Type
(Alias
(Prim
));
4975 Iface_Typ
:= Find_Dispatching_Type
(Abstract_Interface_Alias
(Prim
));
4977 -- Generate the code of the thunk only if the abstract interface type is
4978 -- not an immediate ancestor of Tagged_Type; otherwise the dispatch
4979 -- table associated with the interface is the primary dispatch table.
4981 pragma Assert
(Is_Interface
(Iface_Typ
));
4983 if not Is_Ancestor
(Iface_Typ
, Tagged_Typ
) then
4985 Make_Defining_Identifier
(Loc
,
4986 Chars
=> New_Internal_Name
('T'));
4988 Insert_Actions
(Related_Nod
, New_List
(
4989 Expand_Interface_Thunk
4991 Thunk_Alias
=> Alias
(Prim
),
4992 Thunk_Id
=> Thunk_Id
),
4994 Fill_Secondary_DT_Entry
(Sloc
(Prim
),
4996 Iface_DT_Ptr
=> Find_Interface_ADT
(Tagged_Typ
, Iface_Typ
),
4997 Thunk_Id
=> Thunk_Id
)));
4999 end Register_Interface_DT_Entry
;