1 ------------------------------------------------------------------------------
3 -- GNAT COMPILER COMPONENTS --
9 -- Copyright (C) 1992-2016, 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 3, or (at your option) any later ver- --
14 -- sion. GNAT is distributed in the hope that it will be useful, but WITH- --
15 -- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY --
16 -- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License --
17 -- for more details. You should have received a copy of the GNU General --
18 -- Public License distributed with GNAT; see file COPYING3. If not, go to --
19 -- http://www.gnu.org/licenses for a complete copy of the license. --
21 -- GNAT was originally developed by the GNAT team at New York University. --
22 -- Extensive contributions were provided by Ada Core Technologies Inc. --
24 ------------------------------------------------------------------------------
26 with Aspects
; use Aspects
;
27 with Atree
; use Atree
;
28 with Casing
; use Casing
;
29 with Checks
; use Checks
;
30 with Debug
; use Debug
;
31 with Einfo
; use Einfo
;
32 with Elists
; use Elists
;
33 with Errout
; use Errout
;
34 with Exp_Aggr
; use Exp_Aggr
;
35 with Exp_Ch6
; use Exp_Ch6
;
36 with Exp_Ch7
; use Exp_Ch7
;
37 with Ghost
; use Ghost
;
38 with Inline
; use Inline
;
39 with Itypes
; use Itypes
;
41 with Nlists
; use Nlists
;
42 with Nmake
; use Nmake
;
44 with Restrict
; use Restrict
;
45 with Rident
; use Rident
;
47 with Sem_Aux
; use Sem_Aux
;
48 with Sem_Ch8
; use Sem_Ch8
;
49 with Sem_Ch13
; use Sem_Ch13
;
50 with Sem_Eval
; use Sem_Eval
;
51 with Sem_Res
; use Sem_Res
;
52 with Sem_Type
; use Sem_Type
;
53 with Sem_Util
; use Sem_Util
;
54 with Snames
; use Snames
;
55 with Stand
; use Stand
;
56 with Stringt
; use Stringt
;
57 with Targparm
; use Targparm
;
58 with Tbuild
; use Tbuild
;
59 with Ttypes
; use Ttypes
;
60 with Urealp
; use Urealp
;
61 with Validsw
; use Validsw
;
63 package body Exp_Util
is
65 -----------------------
66 -- Local Subprograms --
67 -----------------------
69 function Build_Task_Array_Image
73 Dyn
: Boolean := False) return Node_Id
;
74 -- Build function to generate the image string for a task that is an array
75 -- component, concatenating the images of each index. To avoid storage
76 -- leaks, the string is built with successive slice assignments. The flag
77 -- Dyn indicates whether this is called for the initialization procedure of
78 -- an array of tasks, or for the name of a dynamically created task that is
79 -- assigned to an indexed component.
81 function Build_Task_Image_Function
85 Res
: Entity_Id
) return Node_Id
;
86 -- Common processing for Task_Array_Image and Task_Record_Image. Build
87 -- function body that computes image.
89 procedure Build_Task_Image_Prefix
98 -- Common processing for Task_Array_Image and Task_Record_Image. Create
99 -- local variables and assign prefix of name to result string.
101 function Build_Task_Record_Image
104 Dyn
: Boolean := False) return Node_Id
;
105 -- Build function to generate the image string for a task that is a record
106 -- component. Concatenate name of variable with that of selector. The flag
107 -- Dyn indicates whether this is called for the initialization procedure of
108 -- record with task components, or for a dynamically created task that is
109 -- assigned to a selected component.
111 procedure Evaluate_Slice_Bounds
(Slice
: Node_Id
);
112 -- Force evaluation of bounds of a slice, which may be given by a range
113 -- or by a subtype indication with or without a constraint.
115 function Make_CW_Equivalent_Type
117 E
: Node_Id
) return Entity_Id
;
118 -- T is a class-wide type entity, E is the initial expression node that
119 -- constrains T in case such as: " X: T := E" or "new T'(E)". This function
120 -- returns the entity of the Equivalent type and inserts on the fly the
121 -- necessary declaration such as:
123 -- type anon is record
124 -- _parent : Root_Type (T); constrained with E discriminants (if any)
125 -- Extension : String (1 .. expr to match size of E);
128 -- This record is compatible with any object of the class of T thanks to
129 -- the first field and has the same size as E thanks to the second.
131 function Make_Literal_Range
133 Literal_Typ
: Entity_Id
) return Node_Id
;
134 -- Produce a Range node whose bounds are:
135 -- Low_Bound (Literal_Type) ..
136 -- Low_Bound (Literal_Type) + (Length (Literal_Typ) - 1)
137 -- this is used for expanding declarations like X : String := "sdfgdfg";
139 -- If the index type of the target array is not integer, we generate:
140 -- Low_Bound (Literal_Type) ..
142 -- (Literal_Type'Pos (Low_Bound (Literal_Type))
143 -- + (Length (Literal_Typ) -1))
145 function Make_Non_Empty_Check
147 N
: Node_Id
) return Node_Id
;
148 -- Produce a boolean expression checking that the unidimensional array
149 -- node N is not empty.
151 function New_Class_Wide_Subtype
153 N
: Node_Id
) return Entity_Id
;
154 -- Create an implicit subtype of CW_Typ attached to node N
156 function Requires_Cleanup_Actions
159 Nested_Constructs
: Boolean) return Boolean;
160 -- Given a list L, determine whether it contains one of the following:
162 -- 1) controlled objects
163 -- 2) library-level tagged types
165 -- Lib_Level is True when the list comes from a construct at the library
166 -- level, and False otherwise. Nested_Constructs is True when any nested
167 -- packages declared in L must be processed, and False otherwise.
169 -------------------------------------
170 -- Activate_Atomic_Synchronization --
171 -------------------------------------
173 procedure Activate_Atomic_Synchronization
(N
: Node_Id
) is
177 case Nkind
(Parent
(N
)) is
179 -- Check for cases of appearing in the prefix of a construct where
180 -- we don't need atomic synchronization for this kind of usage.
183 -- Nothing to do if we are the prefix of an attribute, since we
184 -- do not want an atomic sync operation for things like 'Size.
186 N_Attribute_Reference |
188 -- The N_Reference node is like an attribute
192 -- Nothing to do for a reference to a component (or components)
193 -- of a composite object. Only reads and updates of the object
194 -- as a whole require atomic synchronization (RM C.6 (15)).
196 N_Indexed_Component |
197 N_Selected_Component |
200 -- For all the above cases, nothing to do if we are the prefix
202 if Prefix
(Parent
(N
)) = N
then
209 -- Nothing to do for the identifier in an object renaming declaration,
210 -- the renaming itself does not need atomic synchronization.
212 if Nkind
(Parent
(N
)) = N_Object_Renaming_Declaration
then
216 -- Go ahead and set the flag
218 Set_Atomic_Sync_Required
(N
);
220 -- Generate info message if requested
222 if Warn_On_Atomic_Synchronization
then
227 when N_Selected_Component | N_Expanded_Name
=>
228 Msg_Node
:= Selector_Name
(N
);
230 when N_Explicit_Dereference | N_Indexed_Component
=>
234 pragma Assert
(False);
238 if Present
(Msg_Node
) then
240 ("info: atomic synchronization set for &?N?", Msg_Node
);
243 ("info: atomic synchronization set?N?", N
);
246 end Activate_Atomic_Synchronization
;
248 ----------------------
249 -- Adjust_Condition --
250 ----------------------
252 procedure Adjust_Condition
(N
: Node_Id
) is
259 Loc
: constant Source_Ptr
:= Sloc
(N
);
260 T
: constant Entity_Id
:= Etype
(N
);
264 -- Defend against a call where the argument has no type, or has a
265 -- type that is not Boolean. This can occur because of prior errors.
267 if No
(T
) or else not Is_Boolean_Type
(T
) then
271 -- Apply validity checking if needed
273 if Validity_Checks_On
and Validity_Check_Tests
then
277 -- Immediate return if standard boolean, the most common case,
278 -- where nothing needs to be done.
280 if Base_Type
(T
) = Standard_Boolean
then
284 -- Case of zero/non-zero semantics or non-standard enumeration
285 -- representation. In each case, we rewrite the node as:
287 -- ityp!(N) /= False'Enum_Rep
289 -- where ityp is an integer type with large enough size to hold any
292 if Nonzero_Is_True
(T
) or else Has_Non_Standard_Rep
(T
) then
293 if Esize
(T
) <= Esize
(Standard_Integer
) then
294 Ti
:= Standard_Integer
;
296 Ti
:= Standard_Long_Long_Integer
;
301 Left_Opnd
=> Unchecked_Convert_To
(Ti
, N
),
303 Make_Attribute_Reference
(Loc
,
304 Attribute_Name
=> Name_Enum_Rep
,
306 New_Occurrence_Of
(First_Literal
(T
), Loc
))));
307 Analyze_And_Resolve
(N
, Standard_Boolean
);
310 Rewrite
(N
, Convert_To
(Standard_Boolean
, N
));
311 Analyze_And_Resolve
(N
, Standard_Boolean
);
314 end Adjust_Condition
;
316 ------------------------
317 -- Adjust_Result_Type --
318 ------------------------
320 procedure Adjust_Result_Type
(N
: Node_Id
; T
: Entity_Id
) is
322 -- Ignore call if current type is not Standard.Boolean
324 if Etype
(N
) /= Standard_Boolean
then
328 -- If result is already of correct type, nothing to do. Note that
329 -- this will get the most common case where everything has a type
330 -- of Standard.Boolean.
332 if Base_Type
(T
) = Standard_Boolean
then
337 KP
: constant Node_Kind
:= Nkind
(Parent
(N
));
340 -- If result is to be used as a Condition in the syntax, no need
341 -- to convert it back, since if it was changed to Standard.Boolean
342 -- using Adjust_Condition, that is just fine for this usage.
344 if KP
in N_Raise_xxx_Error
or else KP
in N_Has_Condition
then
347 -- If result is an operand of another logical operation, no need
348 -- to reset its type, since Standard.Boolean is just fine, and
349 -- such operations always do Adjust_Condition on their operands.
351 elsif KP
in N_Op_Boolean
352 or else KP
in N_Short_Circuit
353 or else KP
= N_Op_Not
357 -- Otherwise we perform a conversion from the current type, which
358 -- must be Standard.Boolean, to the desired type.
362 Rewrite
(N
, Convert_To
(T
, N
));
363 Analyze_And_Resolve
(N
, T
);
367 end Adjust_Result_Type
;
369 --------------------------
370 -- Append_Freeze_Action --
371 --------------------------
373 procedure Append_Freeze_Action
(T
: Entity_Id
; N
: Node_Id
) is
377 Ensure_Freeze_Node
(T
);
378 Fnode
:= Freeze_Node
(T
);
380 if No
(Actions
(Fnode
)) then
381 Set_Actions
(Fnode
, New_List
(N
));
383 Append
(N
, Actions
(Fnode
));
386 end Append_Freeze_Action
;
388 ---------------------------
389 -- Append_Freeze_Actions --
390 ---------------------------
392 procedure Append_Freeze_Actions
(T
: Entity_Id
; L
: List_Id
) is
400 Ensure_Freeze_Node
(T
);
401 Fnode
:= Freeze_Node
(T
);
403 if No
(Actions
(Fnode
)) then
404 Set_Actions
(Fnode
, L
);
406 Append_List
(L
, Actions
(Fnode
));
408 end Append_Freeze_Actions
;
410 ------------------------------------
411 -- Build_Allocate_Deallocate_Proc --
412 ------------------------------------
414 procedure Build_Allocate_Deallocate_Proc
416 Is_Allocate
: Boolean)
418 Desig_Typ
: Entity_Id
;
421 Proc_To_Call
: Node_Id
:= Empty
;
424 function Find_Object
(E
: Node_Id
) return Node_Id
;
425 -- Given an arbitrary expression of an allocator, try to find an object
426 -- reference in it, otherwise return the original expression.
428 function Is_Allocate_Deallocate_Proc
(Subp
: Entity_Id
) return Boolean;
429 -- Determine whether subprogram Subp denotes a custom allocate or
436 function Find_Object
(E
: Node_Id
) return Node_Id
is
440 pragma Assert
(Is_Allocate
);
444 if Nkind
(Expr
) = N_Explicit_Dereference
then
445 Expr
:= Prefix
(Expr
);
447 elsif Nkind
(Expr
) = N_Qualified_Expression
then
448 Expr
:= Expression
(Expr
);
450 elsif Nkind
(Expr
) = N_Unchecked_Type_Conversion
then
452 -- When interface class-wide types are involved in allocation,
453 -- the expander introduces several levels of address arithmetic
454 -- to perform dispatch table displacement. In this scenario the
455 -- object appears as:
457 -- Tag_Ptr (Base_Address (<object>'Address))
459 -- Detect this case and utilize the whole expression as the
460 -- "object" since it now points to the proper dispatch table.
462 if Is_RTE
(Etype
(Expr
), RE_Tag_Ptr
) then
465 -- Continue to strip the object
468 Expr
:= Expression
(Expr
);
479 ---------------------------------
480 -- Is_Allocate_Deallocate_Proc --
481 ---------------------------------
483 function Is_Allocate_Deallocate_Proc
(Subp
: Entity_Id
) return Boolean is
485 -- Look for a subprogram body with only one statement which is a
486 -- call to Allocate_Any_Controlled / Deallocate_Any_Controlled.
488 if Ekind
(Subp
) = E_Procedure
489 and then Nkind
(Parent
(Parent
(Subp
))) = N_Subprogram_Body
492 HSS
: constant Node_Id
:=
493 Handled_Statement_Sequence
(Parent
(Parent
(Subp
)));
497 if Present
(Statements
(HSS
))
498 and then Nkind
(First
(Statements
(HSS
))) =
499 N_Procedure_Call_Statement
501 Proc
:= Entity
(Name
(First
(Statements
(HSS
))));
504 Is_RTE
(Proc
, RE_Allocate_Any_Controlled
)
505 or else Is_RTE
(Proc
, RE_Deallocate_Any_Controlled
);
511 end Is_Allocate_Deallocate_Proc
;
513 -- Start of processing for Build_Allocate_Deallocate_Proc
516 -- Obtain the attributes of the allocation / deallocation
518 if Nkind
(N
) = N_Free_Statement
then
519 Expr
:= Expression
(N
);
520 Ptr_Typ
:= Base_Type
(Etype
(Expr
));
521 Proc_To_Call
:= Procedure_To_Call
(N
);
524 if Nkind
(N
) = N_Object_Declaration
then
525 Expr
:= Expression
(N
);
530 -- In certain cases an allocator with a qualified expression may
531 -- be relocated and used as the initialization expression of a
535 -- Obj : Ptr_Typ := new Desig_Typ'(...);
538 -- Tmp : Ptr_Typ := new Desig_Typ'(...);
539 -- Obj : Ptr_Typ := Tmp;
541 -- Since the allocator is always marked as analyzed to avoid infinite
542 -- expansion, it will never be processed by this routine given that
543 -- the designated type needs finalization actions. Detect this case
544 -- and complete the expansion of the allocator.
546 if Nkind
(Expr
) = N_Identifier
547 and then Nkind
(Parent
(Entity
(Expr
))) = N_Object_Declaration
548 and then Nkind
(Expression
(Parent
(Entity
(Expr
)))) = N_Allocator
550 Build_Allocate_Deallocate_Proc
(Parent
(Entity
(Expr
)), True);
554 -- The allocator may have been rewritten into something else in which
555 -- case the expansion performed by this routine does not apply.
557 if Nkind
(Expr
) /= N_Allocator
then
561 Ptr_Typ
:= Base_Type
(Etype
(Expr
));
562 Proc_To_Call
:= Procedure_To_Call
(Expr
);
565 Pool_Id
:= Associated_Storage_Pool
(Ptr_Typ
);
566 Desig_Typ
:= Available_View
(Designated_Type
(Ptr_Typ
));
568 -- Handle concurrent types
570 if Is_Concurrent_Type
(Desig_Typ
)
571 and then Present
(Corresponding_Record_Type
(Desig_Typ
))
573 Desig_Typ
:= Corresponding_Record_Type
(Desig_Typ
);
576 -- Do not process allocations / deallocations without a pool
581 -- Do not process allocations on / deallocations from the secondary
584 elsif Is_RTE
(Pool_Id
, RE_SS_Pool
) then
587 -- Optimize the case where we are using the default Global_Pool_Object,
588 -- and we don't need the heavy finalization machinery.
590 elsif Pool_Id
= RTE
(RE_Global_Pool_Object
)
591 and then not Needs_Finalization
(Desig_Typ
)
595 -- Do not replicate the machinery if the allocator / free has already
596 -- been expanded and has a custom Allocate / Deallocate.
598 elsif Present
(Proc_To_Call
)
599 and then Is_Allocate_Deallocate_Proc
(Proc_To_Call
)
604 if Needs_Finalization
(Desig_Typ
) then
606 -- Certain run-time configurations and targets do not provide support
607 -- for controlled types.
609 if Restriction_Active
(No_Finalization
) then
612 -- Do nothing if the access type may never allocate / deallocate
615 elsif No_Pool_Assigned
(Ptr_Typ
) then
619 -- The allocation / deallocation of a controlled object must be
620 -- chained on / detached from a finalization master.
622 pragma Assert
(Present
(Finalization_Master
(Ptr_Typ
)));
624 -- The only other kind of allocation / deallocation supported by this
625 -- routine is on / from a subpool.
627 elsif Nkind
(Expr
) = N_Allocator
628 and then No
(Subpool_Handle_Name
(Expr
))
634 Loc
: constant Source_Ptr
:= Sloc
(N
);
635 Addr_Id
: constant Entity_Id
:= Make_Temporary
(Loc
, 'A');
636 Alig_Id
: constant Entity_Id
:= Make_Temporary
(Loc
, 'L');
637 Proc_Id
: constant Entity_Id
:= Make_Temporary
(Loc
, 'P');
638 Size_Id
: constant Entity_Id
:= Make_Temporary
(Loc
, 'S');
641 Fin_Addr_Id
: Entity_Id
;
642 Fin_Mas_Act
: Node_Id
;
643 Fin_Mas_Id
: Entity_Id
;
644 Proc_To_Call
: Entity_Id
;
645 Subpool
: Node_Id
:= Empty
;
648 -- Step 1: Construct all the actuals for the call to library routine
649 -- Allocate_Any_Controlled / Deallocate_Any_Controlled.
653 Actuals
:= New_List
(New_Occurrence_Of
(Pool_Id
, Loc
));
659 if Nkind
(Expr
) = N_Allocator
then
660 Subpool
:= Subpool_Handle_Name
(Expr
);
663 -- If a subpool is present it can be an arbitrary name, so make
664 -- the actual by copying the tree.
666 if Present
(Subpool
) then
667 Append_To
(Actuals
, New_Copy_Tree
(Subpool
, New_Sloc
=> Loc
));
669 Append_To
(Actuals
, Make_Null
(Loc
));
672 -- c) Finalization master
674 if Needs_Finalization
(Desig_Typ
) then
675 Fin_Mas_Id
:= Finalization_Master
(Ptr_Typ
);
676 Fin_Mas_Act
:= New_Occurrence_Of
(Fin_Mas_Id
, Loc
);
678 -- Handle the case where the master is actually a pointer to a
679 -- master. This case arises in build-in-place functions.
681 if Is_Access_Type
(Etype
(Fin_Mas_Id
)) then
682 Append_To
(Actuals
, Fin_Mas_Act
);
685 Make_Attribute_Reference
(Loc
,
686 Prefix
=> Fin_Mas_Act
,
687 Attribute_Name
=> Name_Unrestricted_Access
));
690 Append_To
(Actuals
, Make_Null
(Loc
));
693 -- d) Finalize_Address
695 -- Primitive Finalize_Address is never generated in CodePeer mode
696 -- since it contains an Unchecked_Conversion.
698 if Needs_Finalization
(Desig_Typ
) and then not CodePeer_Mode
then
699 Fin_Addr_Id
:= Finalize_Address
(Desig_Typ
);
700 pragma Assert
(Present
(Fin_Addr_Id
));
703 Make_Attribute_Reference
(Loc
,
704 Prefix
=> New_Occurrence_Of
(Fin_Addr_Id
, Loc
),
705 Attribute_Name
=> Name_Unrestricted_Access
));
707 Append_To
(Actuals
, Make_Null
(Loc
));
715 Append_To
(Actuals
, New_Occurrence_Of
(Addr_Id
, Loc
));
716 Append_To
(Actuals
, New_Occurrence_Of
(Size_Id
, Loc
));
718 if Is_Allocate
or else not Is_Class_Wide_Type
(Desig_Typ
) then
719 Append_To
(Actuals
, New_Occurrence_Of
(Alig_Id
, Loc
));
721 -- For deallocation of class-wide types we obtain the value of
722 -- alignment from the Type Specific Record of the deallocated object.
723 -- This is needed because the frontend expansion of class-wide types
724 -- into equivalent types confuses the backend.
730 -- ... because 'Alignment applied to class-wide types is expanded
731 -- into the code that reads the value of alignment from the TSD
732 -- (see Expand_N_Attribute_Reference)
735 Unchecked_Convert_To
(RTE
(RE_Storage_Offset
),
736 Make_Attribute_Reference
(Loc
,
738 Make_Explicit_Dereference
(Loc
, Relocate_Node
(Expr
)),
739 Attribute_Name
=> Name_Alignment
)));
744 if Needs_Finalization
(Desig_Typ
) then
746 Flag_Id
: constant Entity_Id
:= Make_Temporary
(Loc
, 'F');
753 Temp
:= Find_Object
(Expression
(Expr
));
758 -- Processing for allocations where the expression is a subtype
762 and then Is_Entity_Name
(Temp
)
763 and then Is_Type
(Entity
(Temp
))
768 (Needs_Finalization
(Entity
(Temp
))), Loc
);
770 -- The allocation / deallocation of a class-wide object relies
771 -- on a runtime check to determine whether the object is truly
772 -- controlled or not. Depending on this check, the finalization
773 -- machinery will request or reclaim extra storage reserved for
776 elsif Is_Class_Wide_Type
(Desig_Typ
) then
778 -- Detect a special case where interface class-wide types
779 -- are involved as the object appears as:
781 -- Tag_Ptr (Base_Address (<object>'Address))
783 -- The expression already yields the proper tag, generate:
787 if Is_RTE
(Etype
(Temp
), RE_Tag_Ptr
) then
789 Make_Explicit_Dereference
(Loc
,
790 Prefix
=> Relocate_Node
(Temp
));
792 -- In the default case, obtain the tag of the object about
793 -- to be allocated / deallocated. Generate:
799 Make_Attribute_Reference
(Loc
,
800 Prefix
=> Relocate_Node
(Temp
),
801 Attribute_Name
=> Name_Tag
);
805 -- Needs_Finalization (<Param>)
808 Make_Function_Call
(Loc
,
810 New_Occurrence_Of
(RTE
(RE_Needs_Finalization
), Loc
),
811 Parameter_Associations
=> New_List
(Param
));
813 -- Processing for generic actuals
815 elsif Is_Generic_Actual_Type
(Desig_Typ
) then
817 New_Occurrence_Of
(Boolean_Literals
818 (Needs_Finalization
(Base_Type
(Desig_Typ
))), Loc
);
820 -- The object does not require any specialized checks, it is
821 -- known to be controlled.
824 Flag_Expr
:= New_Occurrence_Of
(Standard_True
, Loc
);
827 -- Create the temporary which represents the finalization state
828 -- of the expression. Generate:
830 -- F : constant Boolean := <Flag_Expr>;
833 Make_Object_Declaration
(Loc
,
834 Defining_Identifier
=> Flag_Id
,
835 Constant_Present
=> True,
837 New_Occurrence_Of
(Standard_Boolean
, Loc
),
838 Expression
=> Flag_Expr
));
840 Append_To
(Actuals
, New_Occurrence_Of
(Flag_Id
, Loc
));
843 -- The object is not controlled
846 Append_To
(Actuals
, New_Occurrence_Of
(Standard_False
, Loc
));
853 New_Occurrence_Of
(Boolean_Literals
(Present
(Subpool
)), Loc
));
856 -- Step 2: Build a wrapper Allocate / Deallocate which internally
857 -- calls Allocate_Any_Controlled / Deallocate_Any_Controlled.
859 -- Select the proper routine to call
862 Proc_To_Call
:= RTE
(RE_Allocate_Any_Controlled
);
864 Proc_To_Call
:= RTE
(RE_Deallocate_Any_Controlled
);
867 -- Create a custom Allocate / Deallocate routine which has identical
868 -- profile to that of System.Storage_Pools.
871 Make_Subprogram_Body
(Loc
,
876 Make_Procedure_Specification
(Loc
,
877 Defining_Unit_Name
=> Proc_Id
,
878 Parameter_Specifications
=> New_List
(
880 -- P : Root_Storage_Pool
882 Make_Parameter_Specification
(Loc
,
883 Defining_Identifier
=> Make_Temporary
(Loc
, 'P'),
885 New_Occurrence_Of
(RTE
(RE_Root_Storage_Pool
), Loc
)),
889 Make_Parameter_Specification
(Loc
,
890 Defining_Identifier
=> Addr_Id
,
891 Out_Present
=> Is_Allocate
,
893 New_Occurrence_Of
(RTE
(RE_Address
), Loc
)),
897 Make_Parameter_Specification
(Loc
,
898 Defining_Identifier
=> Size_Id
,
900 New_Occurrence_Of
(RTE
(RE_Storage_Count
), Loc
)),
904 Make_Parameter_Specification
(Loc
,
905 Defining_Identifier
=> Alig_Id
,
907 New_Occurrence_Of
(RTE
(RE_Storage_Count
), Loc
)))),
909 Declarations
=> No_List
,
911 Handled_Statement_Sequence
=>
912 Make_Handled_Sequence_Of_Statements
(Loc
,
913 Statements
=> New_List
(
914 Make_Procedure_Call_Statement
(Loc
,
915 Name
=> New_Occurrence_Of
(Proc_To_Call
, Loc
),
916 Parameter_Associations
=> Actuals
)))));
918 -- The newly generated Allocate / Deallocate becomes the default
919 -- procedure to call when the back end processes the allocation /
923 Set_Procedure_To_Call
(Expr
, Proc_Id
);
925 Set_Procedure_To_Call
(N
, Proc_Id
);
928 end Build_Allocate_Deallocate_Proc
;
930 --------------------------
931 -- Build_Procedure_Form --
932 --------------------------
934 procedure Build_Procedure_Form
(N
: Node_Id
) is
935 Loc
: constant Source_Ptr
:= Sloc
(N
);
936 Subp
: constant Entity_Id
:= Defining_Entity
(N
);
938 Func_Formal
: Entity_Id
;
939 Proc_Formals
: List_Id
;
943 -- No action needed if this transformation was already done, or in case
944 -- of subprogram renaming declarations.
946 if Nkind
(Specification
(N
)) = N_Procedure_Specification
947 or else Nkind
(N
) = N_Subprogram_Renaming_Declaration
952 -- Ditto when dealing with an expression function, where both the
953 -- original expression and the generated declaration end up being
956 if Rewritten_For_C
(Subp
) then
960 Proc_Formals
:= New_List
;
962 -- Create a list of formal parameters with the same types as the
965 Func_Formal
:= First_Formal
(Subp
);
966 while Present
(Func_Formal
) loop
967 Append_To
(Proc_Formals
,
968 Make_Parameter_Specification
(Loc
,
969 Defining_Identifier
=>
970 Make_Defining_Identifier
(Loc
, Chars
(Func_Formal
)),
972 New_Occurrence_Of
(Etype
(Func_Formal
), Loc
)));
974 Next_Formal
(Func_Formal
);
977 -- Add an extra out parameter to carry the function result
980 Name_Buffer
(1 .. Name_Len
) := "RESULT";
981 Append_To
(Proc_Formals
,
982 Make_Parameter_Specification
(Loc
,
983 Defining_Identifier
=>
984 Make_Defining_Identifier
(Loc
, Chars
=> Name_Find
),
986 Parameter_Type
=> New_Occurrence_Of
(Etype
(Subp
), Loc
)));
988 -- The new procedure declaration is inserted immediately after the
989 -- function declaration. The processing in Build_Procedure_Body_Form
990 -- relies on this order.
993 Make_Subprogram_Declaration
(Loc
,
995 Make_Procedure_Specification
(Loc
,
996 Defining_Unit_Name
=>
997 Make_Defining_Identifier
(Loc
, Chars
(Subp
)),
998 Parameter_Specifications
=> Proc_Formals
));
1000 Insert_After_And_Analyze
(Unit_Declaration_Node
(Subp
), Proc_Decl
);
1002 -- Entity of procedure must remain invisible so that it does not
1003 -- overload subsequent references to the original function.
1005 Set_Is_Immediately_Visible
(Defining_Entity
(Proc_Decl
), False);
1007 -- Mark the function as having a procedure form and link the function
1008 -- and its internally built procedure.
1010 Set_Rewritten_For_C
(Subp
);
1011 Set_Corresponding_Procedure
(Subp
, Defining_Entity
(Proc_Decl
));
1012 Set_Corresponding_Function
(Defining_Entity
(Proc_Decl
), Subp
);
1013 end Build_Procedure_Form
;
1015 ------------------------
1016 -- Build_Runtime_Call --
1017 ------------------------
1019 function Build_Runtime_Call
(Loc
: Source_Ptr
; RE
: RE_Id
) return Node_Id
is
1021 -- If entity is not available, we can skip making the call (this avoids
1022 -- junk duplicated error messages in a number of cases).
1024 if not RTE_Available
(RE
) then
1025 return Make_Null_Statement
(Loc
);
1028 Make_Procedure_Call_Statement
(Loc
,
1029 Name
=> New_Occurrence_Of
(RTE
(RE
), Loc
));
1031 end Build_Runtime_Call
;
1033 ------------------------
1034 -- Build_SS_Mark_Call --
1035 ------------------------
1037 function Build_SS_Mark_Call
1039 Mark
: Entity_Id
) return Node_Id
1043 -- Mark : constant Mark_Id := SS_Mark;
1046 Make_Object_Declaration
(Loc
,
1047 Defining_Identifier
=> Mark
,
1048 Constant_Present
=> True,
1049 Object_Definition
=>
1050 New_Occurrence_Of
(RTE
(RE_Mark_Id
), Loc
),
1052 Make_Function_Call
(Loc
,
1053 Name
=> New_Occurrence_Of
(RTE
(RE_SS_Mark
), Loc
)));
1054 end Build_SS_Mark_Call
;
1056 ---------------------------
1057 -- Build_SS_Release_Call --
1058 ---------------------------
1060 function Build_SS_Release_Call
1062 Mark
: Entity_Id
) return Node_Id
1066 -- SS_Release (Mark);
1069 Make_Procedure_Call_Statement
(Loc
,
1071 New_Occurrence_Of
(RTE
(RE_SS_Release
), Loc
),
1072 Parameter_Associations
=> New_List
(
1073 New_Occurrence_Of
(Mark
, Loc
)));
1074 end Build_SS_Release_Call
;
1076 ----------------------------
1077 -- Build_Task_Array_Image --
1078 ----------------------------
1080 -- This function generates the body for a function that constructs the
1081 -- image string for a task that is an array component. The function is
1082 -- local to the init proc for the array type, and is called for each one
1083 -- of the components. The constructed image has the form of an indexed
1084 -- component, whose prefix is the outer variable of the array type.
1085 -- The n-dimensional array type has known indexes Index, Index2...
1087 -- Id_Ref is an indexed component form created by the enclosing init proc.
1088 -- Its successive indexes are Val1, Val2, ... which are the loop variables
1089 -- in the loops that call the individual task init proc on each component.
1091 -- The generated function has the following structure:
1093 -- function F return String is
1094 -- Pref : string renames Task_Name;
1095 -- T1 : String := Index1'Image (Val1);
1097 -- Tn : String := indexn'image (Valn);
1098 -- Len : Integer := T1'Length + ... + Tn'Length + n + 1;
1099 -- -- Len includes commas and the end parentheses.
1100 -- Res : String (1..Len);
1101 -- Pos : Integer := Pref'Length;
1104 -- Res (1 .. Pos) := Pref;
1106 -- Res (Pos) := '(';
1108 -- Res (Pos .. Pos + T1'Length - 1) := T1;
1109 -- Pos := Pos + T1'Length;
1110 -- Res (Pos) := '.';
1113 -- Res (Pos .. Pos + Tn'Length - 1) := Tn;
1114 -- Res (Len) := ')';
1119 -- Needless to say, multidimensional arrays of tasks are rare enough that
1120 -- the bulkiness of this code is not really a concern.
1122 function Build_Task_Array_Image
1126 Dyn
: Boolean := False) return Node_Id
1128 Dims
: constant Nat
:= Number_Dimensions
(A_Type
);
1129 -- Number of dimensions for array of tasks
1131 Temps
: array (1 .. Dims
) of Entity_Id
;
1132 -- Array of temporaries to hold string for each index
1138 -- Total length of generated name
1141 -- Running index for substring assignments
1143 Pref
: constant Entity_Id
:= Make_Temporary
(Loc
, 'P');
1144 -- Name of enclosing variable, prefix of resulting name
1147 -- String to hold result
1150 -- Value of successive indexes
1153 -- Expression to compute total size of string
1156 -- Entity for name at one index position
1158 Decls
: constant List_Id
:= New_List
;
1159 Stats
: constant List_Id
:= New_List
;
1162 -- For a dynamic task, the name comes from the target variable. For a
1163 -- static one it is a formal of the enclosing init proc.
1166 Get_Name_String
(Chars
(Entity
(Prefix
(Id_Ref
))));
1168 Make_Object_Declaration
(Loc
,
1169 Defining_Identifier
=> Pref
,
1170 Object_Definition
=> New_Occurrence_Of
(Standard_String
, Loc
),
1172 Make_String_Literal
(Loc
,
1173 Strval
=> String_From_Name_Buffer
)));
1177 Make_Object_Renaming_Declaration
(Loc
,
1178 Defining_Identifier
=> Pref
,
1179 Subtype_Mark
=> New_Occurrence_Of
(Standard_String
, Loc
),
1180 Name
=> Make_Identifier
(Loc
, Name_uTask_Name
)));
1183 Indx
:= First_Index
(A_Type
);
1184 Val
:= First
(Expressions
(Id_Ref
));
1186 for J
in 1 .. Dims
loop
1187 T
:= Make_Temporary
(Loc
, 'T');
1191 Make_Object_Declaration
(Loc
,
1192 Defining_Identifier
=> T
,
1193 Object_Definition
=> New_Occurrence_Of
(Standard_String
, Loc
),
1195 Make_Attribute_Reference
(Loc
,
1196 Attribute_Name
=> Name_Image
,
1197 Prefix
=> New_Occurrence_Of
(Etype
(Indx
), Loc
),
1198 Expressions
=> New_List
(New_Copy_Tree
(Val
)))));
1204 Sum
:= Make_Integer_Literal
(Loc
, Dims
+ 1);
1210 Make_Attribute_Reference
(Loc
,
1211 Attribute_Name
=> Name_Length
,
1212 Prefix
=> New_Occurrence_Of
(Pref
, Loc
),
1213 Expressions
=> New_List
(Make_Integer_Literal
(Loc
, 1))));
1215 for J
in 1 .. Dims
loop
1220 Make_Attribute_Reference
(Loc
,
1221 Attribute_Name
=> Name_Length
,
1223 New_Occurrence_Of
(Temps
(J
), Loc
),
1224 Expressions
=> New_List
(Make_Integer_Literal
(Loc
, 1))));
1227 Build_Task_Image_Prefix
(Loc
, Len
, Res
, Pos
, Pref
, Sum
, Decls
, Stats
);
1229 Set_Character_Literal_Name
(Char_Code
(Character'Pos ('(')));
1232 Make_Assignment_Statement
(Loc
,
1234 Make_Indexed_Component
(Loc
,
1235 Prefix
=> New_Occurrence_Of
(Res
, Loc
),
1236 Expressions
=> New_List
(New_Occurrence_Of
(Pos
, Loc
))),
1238 Make_Character_Literal
(Loc
,
1240 Char_Literal_Value
=> UI_From_Int
(Character'Pos ('(')))));
1243 Make_Assignment_Statement
(Loc
,
1244 Name
=> New_Occurrence_Of
(Pos
, Loc
),
1247 Left_Opnd
=> New_Occurrence_Of
(Pos
, Loc
),
1248 Right_Opnd
=> Make_Integer_Literal
(Loc
, 1))));
1250 for J
in 1 .. Dims
loop
1253 Make_Assignment_Statement
(Loc
,
1256 Prefix
=> New_Occurrence_Of
(Res
, Loc
),
1259 Low_Bound
=> New_Occurrence_Of
(Pos
, Loc
),
1261 Make_Op_Subtract
(Loc
,
1264 Left_Opnd
=> New_Occurrence_Of
(Pos
, Loc
),
1266 Make_Attribute_Reference
(Loc
,
1267 Attribute_Name
=> Name_Length
,
1269 New_Occurrence_Of
(Temps
(J
), Loc
),
1271 New_List
(Make_Integer_Literal
(Loc
, 1)))),
1272 Right_Opnd
=> Make_Integer_Literal
(Loc
, 1)))),
1274 Expression
=> New_Occurrence_Of
(Temps
(J
), Loc
)));
1278 Make_Assignment_Statement
(Loc
,
1279 Name
=> New_Occurrence_Of
(Pos
, Loc
),
1282 Left_Opnd
=> New_Occurrence_Of
(Pos
, Loc
),
1284 Make_Attribute_Reference
(Loc
,
1285 Attribute_Name
=> Name_Length
,
1286 Prefix
=> New_Occurrence_Of
(Temps
(J
), Loc
),
1288 New_List
(Make_Integer_Literal
(Loc
, 1))))));
1290 Set_Character_Literal_Name
(Char_Code
(Character'Pos (',')));
1293 Make_Assignment_Statement
(Loc
,
1294 Name
=> Make_Indexed_Component
(Loc
,
1295 Prefix
=> New_Occurrence_Of
(Res
, Loc
),
1296 Expressions
=> New_List
(New_Occurrence_Of
(Pos
, Loc
))),
1298 Make_Character_Literal
(Loc
,
1300 Char_Literal_Value
=> UI_From_Int
(Character'Pos (',')))));
1303 Make_Assignment_Statement
(Loc
,
1304 Name
=> New_Occurrence_Of
(Pos
, Loc
),
1307 Left_Opnd
=> New_Occurrence_Of
(Pos
, Loc
),
1308 Right_Opnd
=> Make_Integer_Literal
(Loc
, 1))));
1312 Set_Character_Literal_Name
(Char_Code
(Character'Pos (')')));
1315 Make_Assignment_Statement
(Loc
,
1317 Make_Indexed_Component
(Loc
,
1318 Prefix
=> New_Occurrence_Of
(Res
, Loc
),
1319 Expressions
=> New_List
(New_Occurrence_Of
(Len
, Loc
))),
1321 Make_Character_Literal
(Loc
,
1323 Char_Literal_Value
=> UI_From_Int
(Character'Pos (')')))));
1324 return Build_Task_Image_Function
(Loc
, Decls
, Stats
, Res
);
1325 end Build_Task_Array_Image
;
1327 ----------------------------
1328 -- Build_Task_Image_Decls --
1329 ----------------------------
1331 function Build_Task_Image_Decls
1335 In_Init_Proc
: Boolean := False) return List_Id
1337 Decls
: constant List_Id
:= New_List
;
1338 T_Id
: Entity_Id
:= Empty
;
1340 Expr
: Node_Id
:= Empty
;
1341 Fun
: Node_Id
:= Empty
;
1342 Is_Dyn
: constant Boolean :=
1343 Nkind
(Parent
(Id_Ref
)) = N_Assignment_Statement
1345 Nkind
(Expression
(Parent
(Id_Ref
))) = N_Allocator
;
1348 -- If Discard_Names or No_Implicit_Heap_Allocations are in effect,
1349 -- generate a dummy declaration only.
1351 if Restriction_Active
(No_Implicit_Heap_Allocations
)
1352 or else Global_Discard_Names
1354 T_Id
:= Make_Temporary
(Loc
, 'J');
1359 Make_Object_Declaration
(Loc
,
1360 Defining_Identifier
=> T_Id
,
1361 Object_Definition
=> New_Occurrence_Of
(Standard_String
, Loc
),
1363 Make_String_Literal
(Loc
,
1364 Strval
=> String_From_Name_Buffer
)));
1367 if Nkind
(Id_Ref
) = N_Identifier
1368 or else Nkind
(Id_Ref
) = N_Defining_Identifier
1370 -- For a simple variable, the image of the task is built from
1371 -- the name of the variable. To avoid possible conflict with the
1372 -- anonymous type created for a single protected object, add a
1376 Make_Defining_Identifier
(Loc
,
1377 New_External_Name
(Chars
(Id_Ref
), 'T', 1));
1379 Get_Name_String
(Chars
(Id_Ref
));
1382 Make_String_Literal
(Loc
,
1383 Strval
=> String_From_Name_Buffer
);
1385 elsif Nkind
(Id_Ref
) = N_Selected_Component
then
1387 Make_Defining_Identifier
(Loc
,
1388 New_External_Name
(Chars
(Selector_Name
(Id_Ref
)), 'T'));
1389 Fun
:= Build_Task_Record_Image
(Loc
, Id_Ref
, Is_Dyn
);
1391 elsif Nkind
(Id_Ref
) = N_Indexed_Component
then
1393 Make_Defining_Identifier
(Loc
,
1394 New_External_Name
(Chars
(A_Type
), 'N'));
1396 Fun
:= Build_Task_Array_Image
(Loc
, Id_Ref
, A_Type
, Is_Dyn
);
1400 if Present
(Fun
) then
1401 Append
(Fun
, Decls
);
1402 Expr
:= Make_Function_Call
(Loc
,
1403 Name
=> New_Occurrence_Of
(Defining_Entity
(Fun
), Loc
));
1405 if not In_Init_Proc
then
1406 Set_Uses_Sec_Stack
(Defining_Entity
(Fun
));
1410 Decl
:= Make_Object_Declaration
(Loc
,
1411 Defining_Identifier
=> T_Id
,
1412 Object_Definition
=> New_Occurrence_Of
(Standard_String
, Loc
),
1413 Constant_Present
=> True,
1414 Expression
=> Expr
);
1416 Append
(Decl
, Decls
);
1418 end Build_Task_Image_Decls
;
1420 -------------------------------
1421 -- Build_Task_Image_Function --
1422 -------------------------------
1424 function Build_Task_Image_Function
1428 Res
: Entity_Id
) return Node_Id
1434 Make_Simple_Return_Statement
(Loc
,
1435 Expression
=> New_Occurrence_Of
(Res
, Loc
)));
1437 Spec
:= Make_Function_Specification
(Loc
,
1438 Defining_Unit_Name
=> Make_Temporary
(Loc
, 'F'),
1439 Result_Definition
=> New_Occurrence_Of
(Standard_String
, Loc
));
1441 -- Calls to 'Image use the secondary stack, which must be cleaned up
1442 -- after the task name is built.
1444 return Make_Subprogram_Body
(Loc
,
1445 Specification
=> Spec
,
1446 Declarations
=> Decls
,
1447 Handled_Statement_Sequence
=>
1448 Make_Handled_Sequence_Of_Statements
(Loc
, Statements
=> Stats
));
1449 end Build_Task_Image_Function
;
1451 -----------------------------
1452 -- Build_Task_Image_Prefix --
1453 -----------------------------
1455 procedure Build_Task_Image_Prefix
1457 Len
: out Entity_Id
;
1458 Res
: out Entity_Id
;
1459 Pos
: out Entity_Id
;
1466 Len
:= Make_Temporary
(Loc
, 'L', Sum
);
1469 Make_Object_Declaration
(Loc
,
1470 Defining_Identifier
=> Len
,
1471 Object_Definition
=> New_Occurrence_Of
(Standard_Integer
, Loc
),
1472 Expression
=> Sum
));
1474 Res
:= Make_Temporary
(Loc
, 'R');
1477 Make_Object_Declaration
(Loc
,
1478 Defining_Identifier
=> Res
,
1479 Object_Definition
=>
1480 Make_Subtype_Indication
(Loc
,
1481 Subtype_Mark
=> New_Occurrence_Of
(Standard_String
, Loc
),
1483 Make_Index_Or_Discriminant_Constraint
(Loc
,
1487 Low_Bound
=> Make_Integer_Literal
(Loc
, 1),
1488 High_Bound
=> New_Occurrence_Of
(Len
, Loc
)))))));
1490 -- Indicate that the result is an internal temporary, so it does not
1491 -- receive a bogus initialization when declaration is expanded. This
1492 -- is both efficient, and prevents anomalies in the handling of
1493 -- dynamic objects on the secondary stack.
1495 Set_Is_Internal
(Res
);
1496 Pos
:= Make_Temporary
(Loc
, 'P');
1499 Make_Object_Declaration
(Loc
,
1500 Defining_Identifier
=> Pos
,
1501 Object_Definition
=> New_Occurrence_Of
(Standard_Integer
, Loc
)));
1503 -- Pos := Prefix'Length;
1506 Make_Assignment_Statement
(Loc
,
1507 Name
=> New_Occurrence_Of
(Pos
, Loc
),
1509 Make_Attribute_Reference
(Loc
,
1510 Attribute_Name
=> Name_Length
,
1511 Prefix
=> New_Occurrence_Of
(Prefix
, Loc
),
1512 Expressions
=> New_List
(Make_Integer_Literal
(Loc
, 1)))));
1514 -- Res (1 .. Pos) := Prefix;
1517 Make_Assignment_Statement
(Loc
,
1520 Prefix
=> New_Occurrence_Of
(Res
, Loc
),
1523 Low_Bound
=> Make_Integer_Literal
(Loc
, 1),
1524 High_Bound
=> New_Occurrence_Of
(Pos
, Loc
))),
1526 Expression
=> New_Occurrence_Of
(Prefix
, Loc
)));
1529 Make_Assignment_Statement
(Loc
,
1530 Name
=> New_Occurrence_Of
(Pos
, Loc
),
1533 Left_Opnd
=> New_Occurrence_Of
(Pos
, Loc
),
1534 Right_Opnd
=> Make_Integer_Literal
(Loc
, 1))));
1535 end Build_Task_Image_Prefix
;
1537 -----------------------------
1538 -- Build_Task_Record_Image --
1539 -----------------------------
1541 function Build_Task_Record_Image
1544 Dyn
: Boolean := False) return Node_Id
1547 -- Total length of generated name
1550 -- Index into result
1553 -- String to hold result
1555 Pref
: constant Entity_Id
:= Make_Temporary
(Loc
, 'P');
1556 -- Name of enclosing variable, prefix of resulting name
1559 -- Expression to compute total size of string
1562 -- Entity for selector name
1564 Decls
: constant List_Id
:= New_List
;
1565 Stats
: constant List_Id
:= New_List
;
1568 -- For a dynamic task, the name comes from the target variable. For a
1569 -- static one it is a formal of the enclosing init proc.
1572 Get_Name_String
(Chars
(Entity
(Prefix
(Id_Ref
))));
1574 Make_Object_Declaration
(Loc
,
1575 Defining_Identifier
=> Pref
,
1576 Object_Definition
=> New_Occurrence_Of
(Standard_String
, Loc
),
1578 Make_String_Literal
(Loc
,
1579 Strval
=> String_From_Name_Buffer
)));
1583 Make_Object_Renaming_Declaration
(Loc
,
1584 Defining_Identifier
=> Pref
,
1585 Subtype_Mark
=> New_Occurrence_Of
(Standard_String
, Loc
),
1586 Name
=> Make_Identifier
(Loc
, Name_uTask_Name
)));
1589 Sel
:= Make_Temporary
(Loc
, 'S');
1591 Get_Name_String
(Chars
(Selector_Name
(Id_Ref
)));
1594 Make_Object_Declaration
(Loc
,
1595 Defining_Identifier
=> Sel
,
1596 Object_Definition
=> New_Occurrence_Of
(Standard_String
, Loc
),
1598 Make_String_Literal
(Loc
,
1599 Strval
=> String_From_Name_Buffer
)));
1601 Sum
:= Make_Integer_Literal
(Loc
, Nat
(Name_Len
+ 1));
1607 Make_Attribute_Reference
(Loc
,
1608 Attribute_Name
=> Name_Length
,
1610 New_Occurrence_Of
(Pref
, Loc
),
1611 Expressions
=> New_List
(Make_Integer_Literal
(Loc
, 1))));
1613 Build_Task_Image_Prefix
(Loc
, Len
, Res
, Pos
, Pref
, Sum
, Decls
, Stats
);
1615 Set_Character_Literal_Name
(Char_Code
(Character'Pos ('.')));
1617 -- Res (Pos) := '.';
1620 Make_Assignment_Statement
(Loc
,
1621 Name
=> Make_Indexed_Component
(Loc
,
1622 Prefix
=> New_Occurrence_Of
(Res
, Loc
),
1623 Expressions
=> New_List
(New_Occurrence_Of
(Pos
, Loc
))),
1625 Make_Character_Literal
(Loc
,
1627 Char_Literal_Value
=>
1628 UI_From_Int
(Character'Pos ('.')))));
1631 Make_Assignment_Statement
(Loc
,
1632 Name
=> New_Occurrence_Of
(Pos
, Loc
),
1635 Left_Opnd
=> New_Occurrence_Of
(Pos
, Loc
),
1636 Right_Opnd
=> Make_Integer_Literal
(Loc
, 1))));
1638 -- Res (Pos .. Len) := Selector;
1641 Make_Assignment_Statement
(Loc
,
1642 Name
=> Make_Slice
(Loc
,
1643 Prefix
=> New_Occurrence_Of
(Res
, Loc
),
1646 Low_Bound
=> New_Occurrence_Of
(Pos
, Loc
),
1647 High_Bound
=> New_Occurrence_Of
(Len
, Loc
))),
1648 Expression
=> New_Occurrence_Of
(Sel
, Loc
)));
1650 return Build_Task_Image_Function
(Loc
, Decls
, Stats
, Res
);
1651 end Build_Task_Record_Image
;
1653 -----------------------------
1654 -- Check_Float_Op_Overflow --
1655 -----------------------------
1657 procedure Check_Float_Op_Overflow
(N
: Node_Id
) is
1659 -- Return if no check needed
1661 if not Is_Floating_Point_Type
(Etype
(N
))
1662 or else not (Do_Overflow_Check
(N
) and then Check_Float_Overflow
)
1664 -- In CodePeer_Mode, rely on the overflow check flag being set instead
1665 -- and do not expand the code for float overflow checking.
1667 or else CodePeer_Mode
1672 -- Otherwise we replace the expression by
1674 -- do Tnn : constant ftype := expression;
1675 -- constraint_error when not Tnn'Valid;
1679 Loc
: constant Source_Ptr
:= Sloc
(N
);
1680 Tnn
: constant Entity_Id
:= Make_Temporary
(Loc
, 'T', N
);
1681 Typ
: constant Entity_Id
:= Etype
(N
);
1684 -- Turn off the Do_Overflow_Check flag, since we are doing that work
1685 -- right here. We also set the node as analyzed to prevent infinite
1686 -- recursion from repeating the operation in the expansion.
1688 Set_Do_Overflow_Check
(N
, False);
1689 Set_Analyzed
(N
, True);
1691 -- Do the rewrite to include the check
1694 Make_Expression_With_Actions
(Loc
,
1695 Actions
=> New_List
(
1696 Make_Object_Declaration
(Loc
,
1697 Defining_Identifier
=> Tnn
,
1698 Object_Definition
=> New_Occurrence_Of
(Typ
, Loc
),
1699 Constant_Present
=> True,
1700 Expression
=> Relocate_Node
(N
)),
1701 Make_Raise_Constraint_Error
(Loc
,
1705 Make_Attribute_Reference
(Loc
,
1706 Prefix
=> New_Occurrence_Of
(Tnn
, Loc
),
1707 Attribute_Name
=> Name_Valid
)),
1708 Reason
=> CE_Overflow_Check_Failed
)),
1709 Expression
=> New_Occurrence_Of
(Tnn
, Loc
)));
1711 Analyze_And_Resolve
(N
, Typ
);
1713 end Check_Float_Op_Overflow
;
1715 ----------------------------------
1716 -- Component_May_Be_Bit_Aligned --
1717 ----------------------------------
1719 function Component_May_Be_Bit_Aligned
(Comp
: Entity_Id
) return Boolean is
1723 -- If no component clause, then everything is fine, since the back end
1724 -- never bit-misaligns by default, even if there is a pragma Packed for
1727 if No
(Comp
) or else No
(Component_Clause
(Comp
)) then
1731 UT
:= Underlying_Type
(Etype
(Comp
));
1733 -- It is only array and record types that cause trouble
1735 if not Is_Record_Type
(UT
) and then not Is_Array_Type
(UT
) then
1738 -- If we know that we have a small (64 bits or less) record or small
1739 -- bit-packed array, then everything is fine, since the back end can
1740 -- handle these cases correctly.
1742 elsif Esize
(Comp
) <= 64
1743 and then (Is_Record_Type
(UT
) or else Is_Bit_Packed_Array
(UT
))
1747 -- Otherwise if the component is not byte aligned, we know we have the
1748 -- nasty unaligned case.
1750 elsif Normalized_First_Bit
(Comp
) /= Uint_0
1751 or else Esize
(Comp
) mod System_Storage_Unit
/= Uint_0
1755 -- If we are large and byte aligned, then OK at this level
1760 end Component_May_Be_Bit_Aligned
;
1762 ----------------------------------------
1763 -- Containing_Package_With_Ext_Axioms --
1764 ----------------------------------------
1766 function Containing_Package_With_Ext_Axioms
1767 (E
: Entity_Id
) return Entity_Id
1770 -- E is the package or generic package which is externally axiomatized
1772 if Ekind_In
(E
, E_Generic_Package
, E_Package
)
1773 and then Has_Annotate_Pragma_For_External_Axiomatization
(E
)
1778 -- If E's scope is axiomatized, E is axiomatized
1780 if Present
(Scope
(E
)) then
1782 First_Ax_Parent_Scope
: constant Entity_Id
:=
1783 Containing_Package_With_Ext_Axioms
(Scope
(E
));
1785 if Present
(First_Ax_Parent_Scope
) then
1786 return First_Ax_Parent_Scope
;
1791 -- Otherwise, if E is a package instance, it is axiomatized if the
1792 -- corresponding generic package is axiomatized.
1794 if Ekind
(E
) = E_Package
then
1796 Par
: constant Node_Id
:= Parent
(E
);
1800 if Nkind
(Par
) = N_Defining_Program_Unit_Name
then
1801 Decl
:= Parent
(Par
);
1806 if Present
(Generic_Parent
(Decl
)) then
1808 Containing_Package_With_Ext_Axioms
(Generic_Parent
(Decl
));
1814 end Containing_Package_With_Ext_Axioms
;
1816 -------------------------------
1817 -- Convert_To_Actual_Subtype --
1818 -------------------------------
1820 procedure Convert_To_Actual_Subtype
(Exp
: Entity_Id
) is
1824 Act_ST
:= Get_Actual_Subtype
(Exp
);
1826 if Act_ST
= Etype
(Exp
) then
1829 Rewrite
(Exp
, Convert_To
(Act_ST
, Relocate_Node
(Exp
)));
1830 Analyze_And_Resolve
(Exp
, Act_ST
);
1832 end Convert_To_Actual_Subtype
;
1834 -----------------------------------
1835 -- Corresponding_Runtime_Package --
1836 -----------------------------------
1838 function Corresponding_Runtime_Package
(Typ
: Entity_Id
) return RTU_Id
is
1839 Pkg_Id
: RTU_Id
:= RTU_Null
;
1842 pragma Assert
(Is_Concurrent_Type
(Typ
));
1844 if Ekind
(Typ
) in Protected_Kind
then
1845 if Has_Entries
(Typ
)
1847 -- A protected type without entries that covers an interface and
1848 -- overrides the abstract routines with protected procedures is
1849 -- considered equivalent to a protected type with entries in the
1850 -- context of dispatching select statements. It is sufficient to
1851 -- check for the presence of an interface list in the declaration
1852 -- node to recognize this case.
1854 or else Present
(Interface_List
(Parent
(Typ
)))
1856 -- Protected types with interrupt handlers (when not using a
1857 -- restricted profile) are also considered equivalent to
1858 -- protected types with entries. The types which are used
1859 -- (Static_Interrupt_Protection and Dynamic_Interrupt_Protection)
1860 -- are derived from Protection_Entries.
1862 or else (Has_Attach_Handler
(Typ
) and then not Restricted_Profile
)
1863 or else Has_Interrupt_Handler
(Typ
)
1866 or else Restriction_Active
(No_Entry_Queue
) = False
1867 or else Restriction_Active
(No_Select_Statements
) = False
1868 or else Number_Entries
(Typ
) > 1
1869 or else (Has_Attach_Handler
(Typ
)
1870 and then not Restricted_Profile
)
1872 Pkg_Id
:= System_Tasking_Protected_Objects_Entries
;
1874 Pkg_Id
:= System_Tasking_Protected_Objects_Single_Entry
;
1878 Pkg_Id
:= System_Tasking_Protected_Objects
;
1883 end Corresponding_Runtime_Package
;
1885 -----------------------------------
1886 -- Current_Sem_Unit_Declarations --
1887 -----------------------------------
1889 function Current_Sem_Unit_Declarations
return List_Id
is
1890 U
: Node_Id
:= Unit
(Cunit
(Current_Sem_Unit
));
1894 -- If the current unit is a package body, locate the visible
1895 -- declarations of the package spec.
1897 if Nkind
(U
) = N_Package_Body
then
1898 U
:= Unit
(Library_Unit
(Cunit
(Current_Sem_Unit
)));
1901 if Nkind
(U
) = N_Package_Declaration
then
1902 U
:= Specification
(U
);
1903 Decls
:= Visible_Declarations
(U
);
1907 Set_Visible_Declarations
(U
, Decls
);
1911 Decls
:= Declarations
(U
);
1915 Set_Declarations
(U
, Decls
);
1920 end Current_Sem_Unit_Declarations
;
1922 -----------------------
1923 -- Duplicate_Subexpr --
1924 -----------------------
1926 function Duplicate_Subexpr
1928 Name_Req
: Boolean := False;
1929 Renaming_Req
: Boolean := False) return Node_Id
1932 Remove_Side_Effects
(Exp
, Name_Req
, Renaming_Req
);
1933 return New_Copy_Tree
(Exp
);
1934 end Duplicate_Subexpr
;
1936 ---------------------------------
1937 -- Duplicate_Subexpr_No_Checks --
1938 ---------------------------------
1940 function Duplicate_Subexpr_No_Checks
1942 Name_Req
: Boolean := False;
1943 Renaming_Req
: Boolean := False;
1944 Related_Id
: Entity_Id
:= Empty
;
1945 Is_Low_Bound
: Boolean := False;
1946 Is_High_Bound
: Boolean := False) return Node_Id
1953 Name_Req
=> Name_Req
,
1954 Renaming_Req
=> Renaming_Req
,
1955 Related_Id
=> Related_Id
,
1956 Is_Low_Bound
=> Is_Low_Bound
,
1957 Is_High_Bound
=> Is_High_Bound
);
1959 New_Exp
:= New_Copy_Tree
(Exp
);
1960 Remove_Checks
(New_Exp
);
1962 end Duplicate_Subexpr_No_Checks
;
1964 -----------------------------------
1965 -- Duplicate_Subexpr_Move_Checks --
1966 -----------------------------------
1968 function Duplicate_Subexpr_Move_Checks
1970 Name_Req
: Boolean := False;
1971 Renaming_Req
: Boolean := False) return Node_Id
1976 Remove_Side_Effects
(Exp
, Name_Req
, Renaming_Req
);
1977 New_Exp
:= New_Copy_Tree
(Exp
);
1978 Remove_Checks
(Exp
);
1980 end Duplicate_Subexpr_Move_Checks
;
1982 --------------------
1983 -- Ensure_Defined --
1984 --------------------
1986 procedure Ensure_Defined
(Typ
: Entity_Id
; N
: Node_Id
) is
1990 -- An itype reference must only be created if this is a local itype, so
1991 -- that gigi can elaborate it on the proper objstack.
1993 if Is_Itype
(Typ
) and then Scope
(Typ
) = Current_Scope
then
1994 IR
:= Make_Itype_Reference
(Sloc
(N
));
1995 Set_Itype
(IR
, Typ
);
1996 Insert_Action
(N
, IR
);
2000 --------------------
2001 -- Entry_Names_OK --
2002 --------------------
2004 function Entry_Names_OK
return Boolean is
2007 not Restricted_Profile
2008 and then not Global_Discard_Names
2009 and then not Restriction_Active
(No_Implicit_Heap_Allocations
)
2010 and then not Restriction_Active
(No_Local_Allocators
);
2017 procedure Evaluate_Name
(Nam
: Node_Id
) is
2018 K
: constant Node_Kind
:= Nkind
(Nam
);
2021 -- For an explicit dereference, we simply force the evaluation of the
2022 -- name expression. The dereference provides a value that is the address
2023 -- for the renamed object, and it is precisely this value that we want
2026 if K
= N_Explicit_Dereference
then
2027 Force_Evaluation
(Prefix
(Nam
));
2029 -- For a selected component, we simply evaluate the prefix
2031 elsif K
= N_Selected_Component
then
2032 Evaluate_Name
(Prefix
(Nam
));
2034 -- For an indexed component, or an attribute reference, we evaluate the
2035 -- prefix, which is itself a name, recursively, and then force the
2036 -- evaluation of all the subscripts (or attribute expressions).
2038 elsif Nkind_In
(K
, N_Indexed_Component
, N_Attribute_Reference
) then
2039 Evaluate_Name
(Prefix
(Nam
));
2045 E
:= First
(Expressions
(Nam
));
2046 while Present
(E
) loop
2047 Force_Evaluation
(E
);
2049 if Original_Node
(E
) /= E
then
2050 Set_Do_Range_Check
(E
, Do_Range_Check
(Original_Node
(E
)));
2057 -- For a slice, we evaluate the prefix, as for the indexed component
2058 -- case and then, if there is a range present, either directly or as the
2059 -- constraint of a discrete subtype indication, we evaluate the two
2060 -- bounds of this range.
2062 elsif K
= N_Slice
then
2063 Evaluate_Name
(Prefix
(Nam
));
2064 Evaluate_Slice_Bounds
(Nam
);
2066 -- For a type conversion, the expression of the conversion must be the
2067 -- name of an object, and we simply need to evaluate this name.
2069 elsif K
= N_Type_Conversion
then
2070 Evaluate_Name
(Expression
(Nam
));
2072 -- For a function call, we evaluate the call
2074 elsif K
= N_Function_Call
then
2075 Force_Evaluation
(Nam
);
2077 -- The remaining cases are direct name, operator symbol and character
2078 -- literal. In all these cases, we do nothing, since we want to
2079 -- reevaluate each time the renamed object is used.
2086 ---------------------------
2087 -- Evaluate_Slice_Bounds --
2088 ---------------------------
2090 procedure Evaluate_Slice_Bounds
(Slice
: Node_Id
) is
2091 DR
: constant Node_Id
:= Discrete_Range
(Slice
);
2096 if Nkind
(DR
) = N_Range
then
2097 Force_Evaluation
(Low_Bound
(DR
));
2098 Force_Evaluation
(High_Bound
(DR
));
2100 elsif Nkind
(DR
) = N_Subtype_Indication
then
2101 Constr
:= Constraint
(DR
);
2103 if Nkind
(Constr
) = N_Range_Constraint
then
2104 Rexpr
:= Range_Expression
(Constr
);
2106 Force_Evaluation
(Low_Bound
(Rexpr
));
2107 Force_Evaluation
(High_Bound
(Rexpr
));
2110 end Evaluate_Slice_Bounds
;
2112 ---------------------
2113 -- Evolve_And_Then --
2114 ---------------------
2116 procedure Evolve_And_Then
(Cond
: in out Node_Id
; Cond1
: Node_Id
) is
2122 Make_And_Then
(Sloc
(Cond1
),
2124 Right_Opnd
=> Cond1
);
2126 end Evolve_And_Then
;
2128 --------------------
2129 -- Evolve_Or_Else --
2130 --------------------
2132 procedure Evolve_Or_Else
(Cond
: in out Node_Id
; Cond1
: Node_Id
) is
2138 Make_Or_Else
(Sloc
(Cond1
),
2140 Right_Opnd
=> Cond1
);
2144 -----------------------------------------
2145 -- Expand_Static_Predicates_In_Choices --
2146 -----------------------------------------
2148 procedure Expand_Static_Predicates_In_Choices
(N
: Node_Id
) is
2149 pragma Assert
(Nkind_In
(N
, N_Case_Statement_Alternative
, N_Variant
));
2151 Choices
: constant List_Id
:= Discrete_Choices
(N
);
2159 Choice
:= First
(Choices
);
2160 while Present
(Choice
) loop
2161 Next_C
:= Next
(Choice
);
2163 -- Check for name of subtype with static predicate
2165 if Is_Entity_Name
(Choice
)
2166 and then Is_Type
(Entity
(Choice
))
2167 and then Has_Predicates
(Entity
(Choice
))
2169 -- Loop through entries in predicate list, converting to choices
2170 -- and inserting in the list before the current choice. Note that
2171 -- if the list is empty, corresponding to a False predicate, then
2172 -- no choices are inserted.
2174 P
:= First
(Static_Discrete_Predicate
(Entity
(Choice
)));
2175 while Present
(P
) loop
2177 -- If low bound and high bounds are equal, copy simple choice
2179 if Expr_Value
(Low_Bound
(P
)) = Expr_Value
(High_Bound
(P
)) then
2180 C
:= New_Copy
(Low_Bound
(P
));
2182 -- Otherwise copy a range
2188 -- Change Sloc to referencing choice (rather than the Sloc of
2189 -- the predicate declaration element itself).
2191 Set_Sloc
(C
, Sloc
(Choice
));
2192 Insert_Before
(Choice
, C
);
2196 -- Delete the predicated entry
2201 -- Move to next choice to check
2205 end Expand_Static_Predicates_In_Choices
;
2207 ------------------------------
2208 -- Expand_Subtype_From_Expr --
2209 ------------------------------
2211 -- This function is applicable for both static and dynamic allocation of
2212 -- objects which are constrained by an initial expression. Basically it
2213 -- transforms an unconstrained subtype indication into a constrained one.
2215 -- The expression may also be transformed in certain cases in order to
2216 -- avoid multiple evaluation. In the static allocation case, the general
2221 -- is transformed into
2223 -- Val : Constrained_Subtype_of_T := Maybe_Modified_Expr;
2225 -- Here are the main cases :
2227 -- <if Expr is a Slice>
2228 -- Val : T ([Index_Subtype (Expr)]) := Expr;
2230 -- <elsif Expr is a String Literal>
2231 -- Val : T (T'First .. T'First + Length (string literal) - 1) := Expr;
2233 -- <elsif Expr is Constrained>
2234 -- subtype T is Type_Of_Expr
2237 -- <elsif Expr is an entity_name>
2238 -- Val : T (constraints taken from Expr) := Expr;
2241 -- type Axxx is access all T;
2242 -- Rval : Axxx := Expr'ref;
2243 -- Val : T (constraints taken from Rval) := Rval.all;
2245 -- ??? note: when the Expression is allocated in the secondary stack
2246 -- we could use it directly instead of copying it by declaring
2247 -- Val : T (...) renames Rval.all
2249 procedure Expand_Subtype_From_Expr
2251 Unc_Type
: Entity_Id
;
2252 Subtype_Indic
: Node_Id
;
2254 Related_Id
: Entity_Id
:= Empty
)
2256 Loc
: constant Source_Ptr
:= Sloc
(N
);
2257 Exp_Typ
: constant Entity_Id
:= Etype
(Exp
);
2261 -- In general we cannot build the subtype if expansion is disabled,
2262 -- because internal entities may not have been defined. However, to
2263 -- avoid some cascaded errors, we try to continue when the expression is
2264 -- an array (or string), because it is safe to compute the bounds. It is
2265 -- in fact required to do so even in a generic context, because there
2266 -- may be constants that depend on the bounds of a string literal, both
2267 -- standard string types and more generally arrays of characters.
2269 -- In GNATprove mode, these extra subtypes are not needed
2271 if GNATprove_Mode
then
2275 if not Expander_Active
2276 and then (No
(Etype
(Exp
)) or else not Is_String_Type
(Etype
(Exp
)))
2281 if Nkind
(Exp
) = N_Slice
then
2283 Slice_Type
: constant Entity_Id
:= Etype
(First_Index
(Exp_Typ
));
2286 Rewrite
(Subtype_Indic
,
2287 Make_Subtype_Indication
(Loc
,
2288 Subtype_Mark
=> New_Occurrence_Of
(Unc_Type
, Loc
),
2290 Make_Index_Or_Discriminant_Constraint
(Loc
,
2291 Constraints
=> New_List
2292 (New_Occurrence_Of
(Slice_Type
, Loc
)))));
2294 -- This subtype indication may be used later for constraint checks
2295 -- we better make sure that if a variable was used as a bound of
2296 -- of the original slice, its value is frozen.
2298 Evaluate_Slice_Bounds
(Exp
);
2301 elsif Ekind
(Exp_Typ
) = E_String_Literal_Subtype
then
2302 Rewrite
(Subtype_Indic
,
2303 Make_Subtype_Indication
(Loc
,
2304 Subtype_Mark
=> New_Occurrence_Of
(Unc_Type
, Loc
),
2306 Make_Index_Or_Discriminant_Constraint
(Loc
,
2307 Constraints
=> New_List
(
2308 Make_Literal_Range
(Loc
,
2309 Literal_Typ
=> Exp_Typ
)))));
2311 -- If the type of the expression is an internally generated type it
2312 -- may not be necessary to create a new subtype. However there are two
2313 -- exceptions: references to the current instances, and aliased array
2314 -- object declarations for which the backend needs to create a template.
2316 elsif Is_Constrained
(Exp_Typ
)
2317 and then not Is_Class_Wide_Type
(Unc_Type
)
2319 (Nkind
(N
) /= N_Object_Declaration
2320 or else not Is_Entity_Name
(Expression
(N
))
2321 or else not Comes_From_Source
(Entity
(Expression
(N
)))
2322 or else not Is_Array_Type
(Exp_Typ
)
2323 or else not Aliased_Present
(N
))
2325 if Is_Itype
(Exp_Typ
) then
2327 -- Within an initialization procedure, a selected component
2328 -- denotes a component of the enclosing record, and it appears as
2329 -- an actual in a call to its own initialization procedure. If
2330 -- this component depends on the outer discriminant, we must
2331 -- generate the proper actual subtype for it.
2333 if Nkind
(Exp
) = N_Selected_Component
2334 and then Within_Init_Proc
2337 Decl
: constant Node_Id
:=
2338 Build_Actual_Subtype_Of_Component
(Exp_Typ
, Exp
);
2340 if Present
(Decl
) then
2341 Insert_Action
(N
, Decl
);
2342 T
:= Defining_Identifier
(Decl
);
2348 -- No need to generate a new subtype
2355 T
:= Make_Temporary
(Loc
, 'T');
2358 Make_Subtype_Declaration
(Loc
,
2359 Defining_Identifier
=> T
,
2360 Subtype_Indication
=> New_Occurrence_Of
(Exp_Typ
, Loc
)));
2362 -- This type is marked as an itype even though it has an explicit
2363 -- declaration since otherwise Is_Generic_Actual_Type can get
2364 -- set, resulting in the generation of spurious errors. (See
2365 -- sem_ch8.Analyze_Package_Renaming and sem_type.covers)
2368 Set_Associated_Node_For_Itype
(T
, Exp
);
2371 Rewrite
(Subtype_Indic
, New_Occurrence_Of
(T
, Loc
));
2373 -- Nothing needs to be done for private types with unknown discriminants
2374 -- if the underlying type is not an unconstrained composite type or it
2375 -- is an unchecked union.
2377 elsif Is_Private_Type
(Unc_Type
)
2378 and then Has_Unknown_Discriminants
(Unc_Type
)
2379 and then (not Is_Composite_Type
(Underlying_Type
(Unc_Type
))
2380 or else Is_Constrained
(Underlying_Type
(Unc_Type
))
2381 or else Is_Unchecked_Union
(Underlying_Type
(Unc_Type
)))
2385 -- Case of derived type with unknown discriminants where the parent type
2386 -- also has unknown discriminants.
2388 elsif Is_Record_Type
(Unc_Type
)
2389 and then not Is_Class_Wide_Type
(Unc_Type
)
2390 and then Has_Unknown_Discriminants
(Unc_Type
)
2391 and then Has_Unknown_Discriminants
(Underlying_Type
(Unc_Type
))
2393 -- Nothing to be done if no underlying record view available
2395 if No
(Underlying_Record_View
(Unc_Type
)) then
2398 -- Otherwise use the Underlying_Record_View to create the proper
2399 -- constrained subtype for an object of a derived type with unknown
2403 Remove_Side_Effects
(Exp
);
2404 Rewrite
(Subtype_Indic
,
2405 Make_Subtype_From_Expr
(Exp
, Underlying_Record_View
(Unc_Type
)));
2408 -- Renamings of class-wide interface types require no equivalent
2409 -- constrained type declarations because we only need to reference
2410 -- the tag component associated with the interface. The same is
2411 -- presumably true for class-wide types in general, so this test
2412 -- is broadened to include all class-wide renamings, which also
2413 -- avoids cases of unbounded recursion in Remove_Side_Effects.
2414 -- (Is this really correct, or are there some cases of class-wide
2415 -- renamings that require action in this procedure???)
2418 and then Nkind
(N
) = N_Object_Renaming_Declaration
2419 and then Is_Class_Wide_Type
(Unc_Type
)
2423 -- In Ada 95 nothing to be done if the type of the expression is limited
2424 -- because in this case the expression cannot be copied, and its use can
2425 -- only be by reference.
2427 -- In Ada 2005 the context can be an object declaration whose expression
2428 -- is a function that returns in place. If the nominal subtype has
2429 -- unknown discriminants, the call still provides constraints on the
2430 -- object, and we have to create an actual subtype from it.
2432 -- If the type is class-wide, the expression is dynamically tagged and
2433 -- we do not create an actual subtype either. Ditto for an interface.
2434 -- For now this applies only if the type is immutably limited, and the
2435 -- function being called is build-in-place. This will have to be revised
2436 -- when build-in-place functions are generalized to other types.
2438 elsif Is_Limited_View
(Exp_Typ
)
2440 (Is_Class_Wide_Type
(Exp_Typ
)
2441 or else Is_Interface
(Exp_Typ
)
2442 or else not Has_Unknown_Discriminants
(Exp_Typ
)
2443 or else not Is_Composite_Type
(Unc_Type
))
2447 -- For limited objects initialized with build in place function calls,
2448 -- nothing to be done; otherwise we prematurely introduce an N_Reference
2449 -- node in the expression initializing the object, which breaks the
2450 -- circuitry that detects and adds the additional arguments to the
2453 elsif Is_Build_In_Place_Function_Call
(Exp
) then
2457 Remove_Side_Effects
(Exp
);
2458 Rewrite
(Subtype_Indic
,
2459 Make_Subtype_From_Expr
(Exp
, Unc_Type
, Related_Id
));
2461 end Expand_Subtype_From_Expr
;
2463 ----------------------
2464 -- Finalize_Address --
2465 ----------------------
2467 function Finalize_Address
(Typ
: Entity_Id
) return Entity_Id
is
2468 Utyp
: Entity_Id
:= Typ
;
2471 -- Handle protected class-wide or task class-wide types
2473 if Is_Class_Wide_Type
(Utyp
) then
2474 if Is_Concurrent_Type
(Root_Type
(Utyp
)) then
2475 Utyp
:= Root_Type
(Utyp
);
2477 elsif Is_Private_Type
(Root_Type
(Utyp
))
2478 and then Present
(Full_View
(Root_Type
(Utyp
)))
2479 and then Is_Concurrent_Type
(Full_View
(Root_Type
(Utyp
)))
2481 Utyp
:= Full_View
(Root_Type
(Utyp
));
2485 -- Handle private types
2487 if Is_Private_Type
(Utyp
) and then Present
(Full_View
(Utyp
)) then
2488 Utyp
:= Full_View
(Utyp
);
2491 -- Handle protected and task types
2493 if Is_Concurrent_Type
(Utyp
)
2494 and then Present
(Corresponding_Record_Type
(Utyp
))
2496 Utyp
:= Corresponding_Record_Type
(Utyp
);
2499 Utyp
:= Underlying_Type
(Base_Type
(Utyp
));
2501 -- Deal with untagged derivation of private views. If the parent is
2502 -- now known to be protected, the finalization routine is the one
2503 -- defined on the corresponding record of the ancestor (corresponding
2504 -- records do not automatically inherit operations, but maybe they
2507 if Is_Untagged_Derivation
(Typ
) then
2508 if Is_Protected_Type
(Typ
) then
2509 Utyp
:= Corresponding_Record_Type
(Root_Type
(Base_Type
(Typ
)));
2512 Utyp
:= Underlying_Type
(Root_Type
(Base_Type
(Typ
)));
2514 if Is_Protected_Type
(Utyp
) then
2515 Utyp
:= Corresponding_Record_Type
(Utyp
);
2520 -- If the underlying_type is a subtype, we are dealing with the
2521 -- completion of a private type. We need to access the base type and
2522 -- generate a conversion to it.
2524 if Utyp
/= Base_Type
(Utyp
) then
2525 pragma Assert
(Is_Private_Type
(Typ
));
2527 Utyp
:= Base_Type
(Utyp
);
2530 -- When dealing with an internally built full view for a type with
2531 -- unknown discriminants, use the original record type.
2533 if Is_Underlying_Record_View
(Utyp
) then
2534 Utyp
:= Etype
(Utyp
);
2537 return TSS
(Utyp
, TSS_Finalize_Address
);
2538 end Finalize_Address
;
2540 ------------------------
2541 -- Find_Interface_ADT --
2542 ------------------------
2544 function Find_Interface_ADT
2546 Iface
: Entity_Id
) return Elmt_Id
2549 Typ
: Entity_Id
:= T
;
2552 pragma Assert
(Is_Interface
(Iface
));
2554 -- Handle private types
2556 if Has_Private_Declaration
(Typ
) and then Present
(Full_View
(Typ
)) then
2557 Typ
:= Full_View
(Typ
);
2560 -- Handle access types
2562 if Is_Access_Type
(Typ
) then
2563 Typ
:= Designated_Type
(Typ
);
2566 -- Handle task and protected types implementing interfaces
2568 if Is_Concurrent_Type
(Typ
) then
2569 Typ
:= Corresponding_Record_Type
(Typ
);
2573 (not Is_Class_Wide_Type
(Typ
)
2574 and then Ekind
(Typ
) /= E_Incomplete_Type
);
2576 if Is_Ancestor
(Iface
, Typ
, Use_Full_View
=> True) then
2577 return First_Elmt
(Access_Disp_Table
(Typ
));
2580 ADT
:= Next_Elmt
(Next_Elmt
(First_Elmt
(Access_Disp_Table
(Typ
))));
2582 and then Present
(Related_Type
(Node
(ADT
)))
2583 and then Related_Type
(Node
(ADT
)) /= Iface
2584 and then not Is_Ancestor
(Iface
, Related_Type
(Node
(ADT
)),
2585 Use_Full_View
=> True)
2590 pragma Assert
(Present
(Related_Type
(Node
(ADT
))));
2593 end Find_Interface_ADT
;
2595 ------------------------
2596 -- Find_Interface_Tag --
2597 ------------------------
2599 function Find_Interface_Tag
2601 Iface
: Entity_Id
) return Entity_Id
2604 Found
: Boolean := False;
2605 Typ
: Entity_Id
:= T
;
2607 procedure Find_Tag
(Typ
: Entity_Id
);
2608 -- Internal subprogram used to recursively climb to the ancestors
2614 procedure Find_Tag
(Typ
: Entity_Id
) is
2619 -- This routine does not handle the case in which the interface is an
2620 -- ancestor of Typ. That case is handled by the enclosing subprogram.
2622 pragma Assert
(Typ
/= Iface
);
2624 -- Climb to the root type handling private types
2626 if Present
(Full_View
(Etype
(Typ
))) then
2627 if Full_View
(Etype
(Typ
)) /= Typ
then
2628 Find_Tag
(Full_View
(Etype
(Typ
)));
2631 elsif Etype
(Typ
) /= Typ
then
2632 Find_Tag
(Etype
(Typ
));
2635 -- Traverse the list of interfaces implemented by the type
2638 and then Present
(Interfaces
(Typ
))
2639 and then not (Is_Empty_Elmt_List
(Interfaces
(Typ
)))
2641 -- Skip the tag associated with the primary table
2643 pragma Assert
(Etype
(First_Tag_Component
(Typ
)) = RTE
(RE_Tag
));
2644 AI_Tag
:= Next_Tag_Component
(First_Tag_Component
(Typ
));
2645 pragma Assert
(Present
(AI_Tag
));
2647 AI_Elmt
:= First_Elmt
(Interfaces
(Typ
));
2648 while Present
(AI_Elmt
) loop
2649 AI
:= Node
(AI_Elmt
);
2652 or else Is_Ancestor
(Iface
, AI
, Use_Full_View
=> True)
2658 AI_Tag
:= Next_Tag_Component
(AI_Tag
);
2659 Next_Elmt
(AI_Elmt
);
2664 -- Start of processing for Find_Interface_Tag
2667 pragma Assert
(Is_Interface
(Iface
));
2669 -- Handle access types
2671 if Is_Access_Type
(Typ
) then
2672 Typ
:= Designated_Type
(Typ
);
2675 -- Handle class-wide types
2677 if Is_Class_Wide_Type
(Typ
) then
2678 Typ
:= Root_Type
(Typ
);
2681 -- Handle private types
2683 if Has_Private_Declaration
(Typ
) and then Present
(Full_View
(Typ
)) then
2684 Typ
:= Full_View
(Typ
);
2687 -- Handle entities from the limited view
2689 if Ekind
(Typ
) = E_Incomplete_Type
then
2690 pragma Assert
(Present
(Non_Limited_View
(Typ
)));
2691 Typ
:= Non_Limited_View
(Typ
);
2694 -- Handle task and protected types implementing interfaces
2696 if Is_Concurrent_Type
(Typ
) then
2697 Typ
:= Corresponding_Record_Type
(Typ
);
2700 -- If the interface is an ancestor of the type, then it shared the
2701 -- primary dispatch table.
2703 if Is_Ancestor
(Iface
, Typ
, Use_Full_View
=> True) then
2704 pragma Assert
(Etype
(First_Tag_Component
(Typ
)) = RTE
(RE_Tag
));
2705 return First_Tag_Component
(Typ
);
2707 -- Otherwise we need to search for its associated tag component
2711 pragma Assert
(Found
);
2714 end Find_Interface_Tag
;
2716 ---------------------------
2717 -- Find_Optional_Prim_Op --
2718 ---------------------------
2720 function Find_Optional_Prim_Op
2721 (T
: Entity_Id
; Name
: Name_Id
) return Entity_Id
2724 Typ
: Entity_Id
:= T
;
2728 if Is_Class_Wide_Type
(Typ
) then
2729 Typ
:= Root_Type
(Typ
);
2732 Typ
:= Underlying_Type
(Typ
);
2734 -- Loop through primitive operations
2736 Prim
:= First_Elmt
(Primitive_Operations
(Typ
));
2737 while Present
(Prim
) loop
2740 -- We can retrieve primitive operations by name if it is an internal
2741 -- name. For equality we must check that both of its operands have
2742 -- the same type, to avoid confusion with user-defined equalities
2743 -- than may have a non-symmetric signature.
2745 exit when Chars
(Op
) = Name
2748 or else Etype
(First_Formal
(Op
)) = Etype
(Last_Formal
(Op
)));
2753 return Node
(Prim
); -- Empty if not found
2754 end Find_Optional_Prim_Op
;
2756 ---------------------------
2757 -- Find_Optional_Prim_Op --
2758 ---------------------------
2760 function Find_Optional_Prim_Op
2762 Name
: TSS_Name_Type
) return Entity_Id
2764 Inher_Op
: Entity_Id
:= Empty
;
2765 Own_Op
: Entity_Id
:= Empty
;
2766 Prim_Elmt
: Elmt_Id
;
2767 Prim_Id
: Entity_Id
;
2768 Typ
: Entity_Id
:= T
;
2771 if Is_Class_Wide_Type
(Typ
) then
2772 Typ
:= Root_Type
(Typ
);
2775 Typ
:= Underlying_Type
(Typ
);
2777 -- This search is based on the assertion that the dispatching version
2778 -- of the TSS routine always precedes the real primitive.
2780 Prim_Elmt
:= First_Elmt
(Primitive_Operations
(Typ
));
2781 while Present
(Prim_Elmt
) loop
2782 Prim_Id
:= Node
(Prim_Elmt
);
2784 if Is_TSS
(Prim_Id
, Name
) then
2785 if Present
(Alias
(Prim_Id
)) then
2786 Inher_Op
:= Prim_Id
;
2792 Next_Elmt
(Prim_Elmt
);
2795 if Present
(Own_Op
) then
2797 elsif Present
(Inher_Op
) then
2802 end Find_Optional_Prim_Op
;
2808 function Find_Prim_Op
2809 (T
: Entity_Id
; Name
: Name_Id
) return Entity_Id
2811 Result
: constant Entity_Id
:= Find_Optional_Prim_Op
(T
, Name
);
2814 raise Program_Error
;
2824 function Find_Prim_Op
2826 Name
: TSS_Name_Type
) return Entity_Id
2828 Result
: constant Entity_Id
:= Find_Optional_Prim_Op
(T
, Name
);
2831 raise Program_Error
;
2837 ----------------------------
2838 -- Find_Protection_Object --
2839 ----------------------------
2841 function Find_Protection_Object
(Scop
: Entity_Id
) return Entity_Id
is
2846 while Present
(S
) loop
2847 if Ekind_In
(S
, E_Entry
, E_Entry_Family
, E_Function
, E_Procedure
)
2848 and then Present
(Protection_Object
(S
))
2850 return Protection_Object
(S
);
2856 -- If we do not find a Protection object in the scope chain, then
2857 -- something has gone wrong, most likely the object was never created.
2859 raise Program_Error
;
2860 end Find_Protection_Object
;
2862 --------------------------
2863 -- Find_Protection_Type --
2864 --------------------------
2866 function Find_Protection_Type
(Conc_Typ
: Entity_Id
) return Entity_Id
is
2868 Typ
: Entity_Id
:= Conc_Typ
;
2871 if Is_Concurrent_Type
(Typ
) then
2872 Typ
:= Corresponding_Record_Type
(Typ
);
2875 -- Since restriction violations are not considered serious errors, the
2876 -- expander remains active, but may leave the corresponding record type
2877 -- malformed. In such cases, component _object is not available so do
2880 if not Analyzed
(Typ
) then
2884 Comp
:= First_Component
(Typ
);
2885 while Present
(Comp
) loop
2886 if Chars
(Comp
) = Name_uObject
then
2887 return Base_Type
(Etype
(Comp
));
2890 Next_Component
(Comp
);
2893 -- The corresponding record of a protected type should always have an
2896 raise Program_Error
;
2897 end Find_Protection_Type
;
2899 -----------------------
2900 -- Find_Hook_Context --
2901 -----------------------
2903 function Find_Hook_Context
(N
: Node_Id
) return Node_Id
is
2907 Wrapped_Node
: Node_Id
;
2908 -- Note: if we are in a transient scope, we want to reuse it as
2909 -- the context for actions insertion, if possible. But if N is itself
2910 -- part of the stored actions for the current transient scope,
2911 -- then we need to insert at the appropriate (inner) location in
2912 -- the not as an action on Node_To_Be_Wrapped.
2914 In_Cond_Expr
: constant Boolean := Within_Case_Or_If_Expression
(N
);
2917 -- When the node is inside a case/if expression, the lifetime of any
2918 -- temporary controlled object is extended. Find a suitable insertion
2919 -- node by locating the topmost case or if expressions.
2921 if In_Cond_Expr
then
2924 while Present
(Par
) loop
2925 if Nkind_In
(Original_Node
(Par
), N_Case_Expression
,
2930 -- Prevent the search from going too far
2932 elsif Is_Body_Or_Package_Declaration
(Par
) then
2936 Par
:= Parent
(Par
);
2939 -- The topmost case or if expression is now recovered, but it may
2940 -- still not be the correct place to add generated code. Climb to
2941 -- find a parent that is part of a declarative or statement list,
2942 -- and is not a list of actuals in a call.
2945 while Present
(Par
) loop
2946 if Is_List_Member
(Par
)
2947 and then not Nkind_In
(Par
, N_Component_Association
,
2948 N_Discriminant_Association
,
2949 N_Parameter_Association
,
2950 N_Pragma_Argument_Association
)
2951 and then not Nkind_In
2952 (Parent
(Par
), N_Function_Call
,
2953 N_Procedure_Call_Statement
,
2954 N_Entry_Call_Statement
)
2959 -- Prevent the search from going too far
2961 elsif Is_Body_Or_Package_Declaration
(Par
) then
2965 Par
:= Parent
(Par
);
2972 while Present
(Par
) loop
2974 -- Keep climbing past various operators
2976 if Nkind
(Parent
(Par
)) in N_Op
2977 or else Nkind_In
(Parent
(Par
), N_And_Then
, N_Or_Else
)
2979 Par
:= Parent
(Par
);
2987 -- The node may be located in a pragma in which case return the
2990 -- pragma Precondition (... and then Ctrl_Func_Call ...);
2992 -- Similar case occurs when the node is related to an object
2993 -- declaration or assignment:
2995 -- Obj [: Some_Typ] := ... and then Ctrl_Func_Call ...;
2997 -- Another case to consider is when the node is part of a return
3000 -- return ... and then Ctrl_Func_Call ...;
3002 -- Another case is when the node acts as a formal in a procedure
3005 -- Proc (... and then Ctrl_Func_Call ...);
3007 if Scope_Is_Transient
then
3008 Wrapped_Node
:= Node_To_Be_Wrapped
;
3010 Wrapped_Node
:= Empty
;
3013 while Present
(Par
) loop
3014 if Par
= Wrapped_Node
3015 or else Nkind_In
(Par
, N_Assignment_Statement
,
3016 N_Object_Declaration
,
3018 N_Procedure_Call_Statement
,
3019 N_Simple_Return_Statement
)
3023 -- Prevent the search from going too far
3025 elsif Is_Body_Or_Package_Declaration
(Par
) then
3029 Par
:= Parent
(Par
);
3032 -- Return the topmost short circuit operator
3036 end Find_Hook_Context
;
3038 ------------------------------
3039 -- Following_Address_Clause --
3040 ------------------------------
3042 function Following_Address_Clause
(D
: Node_Id
) return Node_Id
is
3043 Id
: constant Entity_Id
:= Defining_Identifier
(D
);
3047 function Check_Decls
(D
: Node_Id
) return Node_Id
;
3048 -- This internal function differs from the main function in that it
3049 -- gets called to deal with a following package private part, and
3050 -- it checks declarations starting with D (the main function checks
3051 -- declarations following D). If D is Empty, then Empty is returned.
3057 function Check_Decls
(D
: Node_Id
) return Node_Id
is
3062 while Present
(Decl
) loop
3063 if Nkind
(Decl
) = N_At_Clause
3064 and then Chars
(Identifier
(Decl
)) = Chars
(Id
)
3068 elsif Nkind
(Decl
) = N_Attribute_Definition_Clause
3069 and then Chars
(Decl
) = Name_Address
3070 and then Chars
(Name
(Decl
)) = Chars
(Id
)
3078 -- Otherwise not found, return Empty
3083 -- Start of processing for Following_Address_Clause
3086 -- If parser detected no address clause for the identifier in question,
3087 -- then the answer is a quick NO, without the need for a search.
3089 if not Get_Name_Table_Boolean1
(Chars
(Id
)) then
3093 -- Otherwise search current declarative unit
3095 Result
:= Check_Decls
(Next
(D
));
3097 if Present
(Result
) then
3101 -- Check for possible package private part following
3105 if Nkind
(Par
) = N_Package_Specification
3106 and then Visible_Declarations
(Par
) = List_Containing
(D
)
3107 and then Present
(Private_Declarations
(Par
))
3109 -- Private part present, check declarations there
3111 return Check_Decls
(First
(Private_Declarations
(Par
)));
3114 -- No private part, clause not found, return Empty
3118 end Following_Address_Clause
;
3120 ----------------------
3121 -- Force_Evaluation --
3122 ----------------------
3124 procedure Force_Evaluation
3126 Name_Req
: Boolean := False;
3127 Related_Id
: Entity_Id
:= Empty
;
3128 Is_Low_Bound
: Boolean := False;
3129 Is_High_Bound
: Boolean := False;
3130 Mode
: Force_Evaluation_Mode
:= Relaxed
)
3135 Name_Req
=> Name_Req
,
3136 Variable_Ref
=> True,
3137 Renaming_Req
=> False,
3138 Related_Id
=> Related_Id
,
3139 Is_Low_Bound
=> Is_Low_Bound
,
3140 Is_High_Bound
=> Is_High_Bound
,
3141 Check_Side_Effects
=>
3142 Is_Static_Expression
(Exp
)
3143 or else Mode
= Relaxed
);
3144 end Force_Evaluation
;
3146 ---------------------------------
3147 -- Fully_Qualified_Name_String --
3148 ---------------------------------
3150 function Fully_Qualified_Name_String
3152 Append_NUL
: Boolean := True) return String_Id
3154 procedure Internal_Full_Qualified_Name
(E
: Entity_Id
);
3155 -- Compute recursively the qualified name without NUL at the end, adding
3156 -- it to the currently started string being generated
3158 ----------------------------------
3159 -- Internal_Full_Qualified_Name --
3160 ----------------------------------
3162 procedure Internal_Full_Qualified_Name
(E
: Entity_Id
) is
3166 -- Deal properly with child units
3168 if Nkind
(E
) = N_Defining_Program_Unit_Name
then
3169 Ent
:= Defining_Identifier
(E
);
3174 -- Compute qualification recursively (only "Standard" has no scope)
3176 if Present
(Scope
(Scope
(Ent
))) then
3177 Internal_Full_Qualified_Name
(Scope
(Ent
));
3178 Store_String_Char
(Get_Char_Code
('.'));
3181 -- Every entity should have a name except some expanded blocks
3182 -- don't bother about those.
3184 if Chars
(Ent
) = No_Name
then
3188 -- Generates the entity name in upper case
3190 Get_Decoded_Name_String
(Chars
(Ent
));
3192 Store_String_Chars
(Name_Buffer
(1 .. Name_Len
));
3194 end Internal_Full_Qualified_Name
;
3196 -- Start of processing for Full_Qualified_Name
3200 Internal_Full_Qualified_Name
(E
);
3203 Store_String_Char
(Get_Char_Code
(ASCII
.NUL
));
3207 end Fully_Qualified_Name_String
;
3209 ------------------------
3210 -- Generate_Poll_Call --
3211 ------------------------
3213 procedure Generate_Poll_Call
(N
: Node_Id
) is
3215 -- No poll call if polling not active
3217 if not Polling_Required
then
3220 -- Otherwise generate require poll call
3223 Insert_Before_And_Analyze
(N
,
3224 Make_Procedure_Call_Statement
(Sloc
(N
),
3225 Name
=> New_Occurrence_Of
(RTE
(RE_Poll
), Sloc
(N
))));
3227 end Generate_Poll_Call
;
3229 ---------------------------------
3230 -- Get_Current_Value_Condition --
3231 ---------------------------------
3233 -- Note: the implementation of this procedure is very closely tied to the
3234 -- implementation of Set_Current_Value_Condition. In the Get procedure, we
3235 -- interpret Current_Value fields set by the Set procedure, so the two
3236 -- procedures need to be closely coordinated.
3238 procedure Get_Current_Value_Condition
3243 Loc
: constant Source_Ptr
:= Sloc
(Var
);
3244 Ent
: constant Entity_Id
:= Entity
(Var
);
3246 procedure Process_Current_Value_Condition
3249 -- N is an expression which holds either True (S = True) or False (S =
3250 -- False) in the condition. This procedure digs out the expression and
3251 -- if it refers to Ent, sets Op and Val appropriately.
3253 -------------------------------------
3254 -- Process_Current_Value_Condition --
3255 -------------------------------------
3257 procedure Process_Current_Value_Condition
3262 Prev_Cond
: Node_Id
;
3272 -- Deal with NOT operators, inverting sense
3274 while Nkind
(Cond
) = N_Op_Not
loop
3275 Cond
:= Right_Opnd
(Cond
);
3279 -- Deal with conversions, qualifications, and expressions with
3282 while Nkind_In
(Cond
,
3284 N_Qualified_Expression
,
3285 N_Expression_With_Actions
)
3287 Cond
:= Expression
(Cond
);
3290 exit when Cond
= Prev_Cond
;
3293 -- Deal with AND THEN and AND cases
3295 if Nkind_In
(Cond
, N_And_Then
, N_Op_And
) then
3297 -- Don't ever try to invert a condition that is of the form of an
3298 -- AND or AND THEN (since we are not doing sufficiently general
3299 -- processing to allow this).
3301 if Sens
= False then
3307 -- Recursively process AND and AND THEN branches
3309 Process_Current_Value_Condition
(Left_Opnd
(Cond
), True);
3311 if Op
/= N_Empty
then
3315 Process_Current_Value_Condition
(Right_Opnd
(Cond
), True);
3318 -- Case of relational operator
3320 elsif Nkind
(Cond
) in N_Op_Compare
then
3323 -- Invert sense of test if inverted test
3325 if Sens
= False then
3327 when N_Op_Eq
=> Op
:= N_Op_Ne
;
3328 when N_Op_Ne
=> Op
:= N_Op_Eq
;
3329 when N_Op_Lt
=> Op
:= N_Op_Ge
;
3330 when N_Op_Gt
=> Op
:= N_Op_Le
;
3331 when N_Op_Le
=> Op
:= N_Op_Gt
;
3332 when N_Op_Ge
=> Op
:= N_Op_Lt
;
3333 when others => raise Program_Error
;
3337 -- Case of entity op value
3339 if Is_Entity_Name
(Left_Opnd
(Cond
))
3340 and then Ent
= Entity
(Left_Opnd
(Cond
))
3341 and then Compile_Time_Known_Value
(Right_Opnd
(Cond
))
3343 Val
:= Right_Opnd
(Cond
);
3345 -- Case of value op entity
3347 elsif Is_Entity_Name
(Right_Opnd
(Cond
))
3348 and then Ent
= Entity
(Right_Opnd
(Cond
))
3349 and then Compile_Time_Known_Value
(Left_Opnd
(Cond
))
3351 Val
:= Left_Opnd
(Cond
);
3353 -- We are effectively swapping operands
3356 when N_Op_Eq
=> null;
3357 when N_Op_Ne
=> null;
3358 when N_Op_Lt
=> Op
:= N_Op_Gt
;
3359 when N_Op_Gt
=> Op
:= N_Op_Lt
;
3360 when N_Op_Le
=> Op
:= N_Op_Ge
;
3361 when N_Op_Ge
=> Op
:= N_Op_Le
;
3362 when others => raise Program_Error
;
3371 elsif Nkind_In
(Cond
,
3373 N_Qualified_Expression
,
3374 N_Expression_With_Actions
)
3376 Cond
:= Expression
(Cond
);
3378 -- Case of Boolean variable reference, return as though the
3379 -- reference had said var = True.
3382 if Is_Entity_Name
(Cond
) and then Ent
= Entity
(Cond
) then
3383 Val
:= New_Occurrence_Of
(Standard_True
, Sloc
(Cond
));
3385 if Sens
= False then
3392 end Process_Current_Value_Condition
;
3394 -- Start of processing for Get_Current_Value_Condition
3400 -- Immediate return, nothing doing, if this is not an object
3402 if Ekind
(Ent
) not in Object_Kind
then
3406 -- Otherwise examine current value
3409 CV
: constant Node_Id
:= Current_Value
(Ent
);
3414 -- If statement. Condition is known true in THEN section, known False
3415 -- in any ELSIF or ELSE part, and unknown outside the IF statement.
3417 if Nkind
(CV
) = N_If_Statement
then
3419 -- Before start of IF statement
3421 if Loc
< Sloc
(CV
) then
3424 -- After end of IF statement
3426 elsif Loc
>= Sloc
(CV
) + Text_Ptr
(UI_To_Int
(End_Span
(CV
))) then
3430 -- At this stage we know that we are within the IF statement, but
3431 -- unfortunately, the tree does not record the SLOC of the ELSE so
3432 -- we cannot use a simple SLOC comparison to distinguish between
3433 -- the then/else statements, so we have to climb the tree.
3440 while Parent
(N
) /= CV
loop
3443 -- If we fall off the top of the tree, then that's odd, but
3444 -- perhaps it could occur in some error situation, and the
3445 -- safest response is simply to assume that the outcome of
3446 -- the condition is unknown. No point in bombing during an
3447 -- attempt to optimize things.
3454 -- Now we have N pointing to a node whose parent is the IF
3455 -- statement in question, so now we can tell if we are within
3456 -- the THEN statements.
3458 if Is_List_Member
(N
)
3459 and then List_Containing
(N
) = Then_Statements
(CV
)
3463 -- If the variable reference does not come from source, we
3464 -- cannot reliably tell whether it appears in the else part.
3465 -- In particular, if it appears in generated code for a node
3466 -- that requires finalization, it may be attached to a list
3467 -- that has not been yet inserted into the code. For now,
3468 -- treat it as unknown.
3470 elsif not Comes_From_Source
(N
) then
3473 -- Otherwise we must be in ELSIF or ELSE part
3480 -- ELSIF part. Condition is known true within the referenced
3481 -- ELSIF, known False in any subsequent ELSIF or ELSE part,
3482 -- and unknown before the ELSE part or after the IF statement.
3484 elsif Nkind
(CV
) = N_Elsif_Part
then
3486 -- if the Elsif_Part had condition_actions, the elsif has been
3487 -- rewritten as a nested if, and the original elsif_part is
3488 -- detached from the tree, so there is no way to obtain useful
3489 -- information on the current value of the variable.
3490 -- Can this be improved ???
3492 if No
(Parent
(CV
)) then
3498 -- If the tree has been otherwise rewritten there is nothing
3499 -- else to be done either.
3501 if Nkind
(Stm
) /= N_If_Statement
then
3505 -- Before start of ELSIF part
3507 if Loc
< Sloc
(CV
) then
3510 -- After end of IF statement
3512 elsif Loc
>= Sloc
(Stm
) +
3513 Text_Ptr
(UI_To_Int
(End_Span
(Stm
)))
3518 -- Again we lack the SLOC of the ELSE, so we need to climb the
3519 -- tree to see if we are within the ELSIF part in question.
3526 while Parent
(N
) /= Stm
loop
3529 -- If we fall off the top of the tree, then that's odd, but
3530 -- perhaps it could occur in some error situation, and the
3531 -- safest response is simply to assume that the outcome of
3532 -- the condition is unknown. No point in bombing during an
3533 -- attempt to optimize things.
3540 -- Now we have N pointing to a node whose parent is the IF
3541 -- statement in question, so see if is the ELSIF part we want.
3542 -- the THEN statements.
3547 -- Otherwise we must be in subsequent ELSIF or ELSE part
3554 -- Iteration scheme of while loop. The condition is known to be
3555 -- true within the body of the loop.
3557 elsif Nkind
(CV
) = N_Iteration_Scheme
then
3559 Loop_Stmt
: constant Node_Id
:= Parent
(CV
);
3562 -- Before start of body of loop
3564 if Loc
< Sloc
(Loop_Stmt
) then
3567 -- After end of LOOP statement
3569 elsif Loc
>= Sloc
(End_Label
(Loop_Stmt
)) then
3572 -- We are within the body of the loop
3579 -- All other cases of Current_Value settings
3585 -- If we fall through here, then we have a reportable condition, Sens
3586 -- is True if the condition is true and False if it needs inverting.
3588 Process_Current_Value_Condition
(Condition
(CV
), Sens
);
3590 end Get_Current_Value_Condition
;
3592 ---------------------
3593 -- Get_Stream_Size --
3594 ---------------------
3596 function Get_Stream_Size
(E
: Entity_Id
) return Uint
is
3598 -- If we have a Stream_Size clause for this type use it
3600 if Has_Stream_Size_Clause
(E
) then
3601 return Static_Integer
(Expression
(Stream_Size_Clause
(E
)));
3603 -- Otherwise the Stream_Size if the size of the type
3608 end Get_Stream_Size
;
3610 ---------------------------
3611 -- Has_Access_Constraint --
3612 ---------------------------
3614 function Has_Access_Constraint
(E
: Entity_Id
) return Boolean is
3616 T
: constant Entity_Id
:= Etype
(E
);
3619 if Has_Per_Object_Constraint
(E
) and then Has_Discriminants
(T
) then
3620 Disc
:= First_Discriminant
(T
);
3621 while Present
(Disc
) loop
3622 if Is_Access_Type
(Etype
(Disc
)) then
3626 Next_Discriminant
(Disc
);
3633 end Has_Access_Constraint
;
3635 -----------------------------------------------------
3636 -- Has_Annotate_Pragma_For_External_Axiomatization --
3637 -----------------------------------------------------
3639 function Has_Annotate_Pragma_For_External_Axiomatization
3640 (E
: Entity_Id
) return Boolean
3642 function Is_Annotate_Pragma_For_External_Axiomatization
3643 (N
: Node_Id
) return Boolean;
3644 -- Returns whether N is
3645 -- pragma Annotate (GNATprove, External_Axiomatization);
3647 ----------------------------------------------------
3648 -- Is_Annotate_Pragma_For_External_Axiomatization --
3649 ----------------------------------------------------
3651 -- The general form of pragma Annotate is
3653 -- pragma Annotate (IDENTIFIER [, IDENTIFIER {, ARG}]);
3654 -- ARG ::= NAME | EXPRESSION
3656 -- The first two arguments are by convention intended to refer to an
3657 -- external tool and a tool-specific function. These arguments are
3660 -- The following is used to annotate a package specification which
3661 -- GNATprove should treat specially, because the axiomatization of
3662 -- this unit is given by the user instead of being automatically
3665 -- pragma Annotate (GNATprove, External_Axiomatization);
3667 function Is_Annotate_Pragma_For_External_Axiomatization
3668 (N
: Node_Id
) return Boolean
3670 Name_GNATprove
: constant String :=
3672 Name_External_Axiomatization
: constant String :=
3673 "external_axiomatization";
3677 if Nkind
(N
) = N_Pragma
3678 and then Get_Pragma_Id
(Pragma_Name
(N
)) = Pragma_Annotate
3679 and then List_Length
(Pragma_Argument_Associations
(N
)) = 2
3682 Arg1
: constant Node_Id
:=
3683 First
(Pragma_Argument_Associations
(N
));
3684 Arg2
: constant Node_Id
:= Next
(Arg1
);
3689 -- Fill in Name_Buffer with Name_GNATprove first, and then with
3690 -- Name_External_Axiomatization so that Name_Find returns the
3691 -- corresponding name. This takes care of all possible casings.
3694 Add_Str_To_Name_Buffer
(Name_GNATprove
);
3698 Add_Str_To_Name_Buffer
(Name_External_Axiomatization
);
3701 return Chars
(Get_Pragma_Arg
(Arg1
)) = Nam1
3703 Chars
(Get_Pragma_Arg
(Arg2
)) = Nam2
;
3709 end Is_Annotate_Pragma_For_External_Axiomatization
;
3714 Vis_Decls
: List_Id
;
3717 -- Start of processing for Has_Annotate_Pragma_For_External_Axiomatization
3720 if Nkind
(Parent
(E
)) = N_Defining_Program_Unit_Name
then
3721 Decl
:= Parent
(Parent
(E
));
3726 Vis_Decls
:= Visible_Declarations
(Decl
);
3728 N
:= First
(Vis_Decls
);
3729 while Present
(N
) loop
3731 -- Skip declarations generated by the frontend. Skip all pragmas
3732 -- that are not the desired Annotate pragma. Stop the search on
3733 -- the first non-pragma source declaration.
3735 if Comes_From_Source
(N
) then
3736 if Nkind
(N
) = N_Pragma
then
3737 if Is_Annotate_Pragma_For_External_Axiomatization
(N
) then
3749 end Has_Annotate_Pragma_For_External_Axiomatization
;
3751 --------------------
3752 -- Homonym_Number --
3753 --------------------
3755 function Homonym_Number
(Subp
: Entity_Id
) return Nat
is
3761 Hom
:= Homonym
(Subp
);
3762 while Present
(Hom
) loop
3763 if Scope
(Hom
) = Scope
(Subp
) then
3767 Hom
:= Homonym
(Hom
);
3773 -----------------------------------
3774 -- In_Library_Level_Package_Body --
3775 -----------------------------------
3777 function In_Library_Level_Package_Body
(Id
: Entity_Id
) return Boolean is
3779 -- First determine whether the entity appears at the library level, then
3780 -- look at the containing unit.
3782 if Is_Library_Level_Entity
(Id
) then
3784 Container
: constant Node_Id
:= Cunit
(Get_Source_Unit
(Id
));
3787 return Nkind
(Unit
(Container
)) = N_Package_Body
;
3792 end In_Library_Level_Package_Body
;
3794 ------------------------------
3795 -- In_Unconditional_Context --
3796 ------------------------------
3798 function In_Unconditional_Context
(Node
: Node_Id
) return Boolean is
3803 while Present
(P
) loop
3805 when N_Subprogram_Body
=>
3808 when N_If_Statement
=>
3811 when N_Loop_Statement
=>
3814 when N_Case_Statement
=>
3823 end In_Unconditional_Context
;
3829 procedure Insert_Action
(Assoc_Node
: Node_Id
; Ins_Action
: Node_Id
) is
3831 if Present
(Ins_Action
) then
3832 Insert_Actions
(Assoc_Node
, New_List
(Ins_Action
));
3836 -- Version with check(s) suppressed
3838 procedure Insert_Action
3839 (Assoc_Node
: Node_Id
; Ins_Action
: Node_Id
; Suppress
: Check_Id
)
3842 Insert_Actions
(Assoc_Node
, New_List
(Ins_Action
), Suppress
);
3845 -------------------------
3846 -- Insert_Action_After --
3847 -------------------------
3849 procedure Insert_Action_After
3850 (Assoc_Node
: Node_Id
;
3851 Ins_Action
: Node_Id
)
3854 Insert_Actions_After
(Assoc_Node
, New_List
(Ins_Action
));
3855 end Insert_Action_After
;
3857 --------------------
3858 -- Insert_Actions --
3859 --------------------
3861 procedure Insert_Actions
(Assoc_Node
: Node_Id
; Ins_Actions
: List_Id
) is
3865 Wrapped_Node
: Node_Id
:= Empty
;
3868 if No
(Ins_Actions
) or else Is_Empty_List
(Ins_Actions
) then
3872 -- Ignore insert of actions from inside default expression (or other
3873 -- similar "spec expression") in the special spec-expression analyze
3874 -- mode. Any insertions at this point have no relevance, since we are
3875 -- only doing the analyze to freeze the types of any static expressions.
3876 -- See section "Handling of Default Expressions" in the spec of package
3877 -- Sem for further details.
3879 if In_Spec_Expression
then
3883 -- If the action derives from stuff inside a record, then the actions
3884 -- are attached to the current scope, to be inserted and analyzed on
3885 -- exit from the scope. The reason for this is that we may also be
3886 -- generating freeze actions at the same time, and they must eventually
3887 -- be elaborated in the correct order.
3889 if Is_Record_Type
(Current_Scope
)
3890 and then not Is_Frozen
(Current_Scope
)
3892 if No
(Scope_Stack
.Table
3893 (Scope_Stack
.Last
).Pending_Freeze_Actions
)
3895 Scope_Stack
.Table
(Scope_Stack
.Last
).Pending_Freeze_Actions
:=
3900 Scope_Stack
.Table
(Scope_Stack
.Last
).Pending_Freeze_Actions
);
3906 -- We now intend to climb up the tree to find the right point to
3907 -- insert the actions. We start at Assoc_Node, unless this node is a
3908 -- subexpression in which case we start with its parent. We do this for
3909 -- two reasons. First it speeds things up. Second, if Assoc_Node is
3910 -- itself one of the special nodes like N_And_Then, then we assume that
3911 -- an initial request to insert actions for such a node does not expect
3912 -- the actions to get deposited in the node for later handling when the
3913 -- node is expanded, since clearly the node is being dealt with by the
3914 -- caller. Note that in the subexpression case, N is always the child we
3917 -- N_Raise_xxx_Error is an annoying special case, it is a statement
3918 -- if it has type Standard_Void_Type, and a subexpression otherwise.
3919 -- Procedure calls, and similarly procedure attribute references, are
3922 if Nkind
(Assoc_Node
) in N_Subexpr
3923 and then (Nkind
(Assoc_Node
) not in N_Raise_xxx_Error
3924 or else Etype
(Assoc_Node
) /= Standard_Void_Type
)
3925 and then Nkind
(Assoc_Node
) /= N_Procedure_Call_Statement
3926 and then (Nkind
(Assoc_Node
) /= N_Attribute_Reference
3927 or else not Is_Procedure_Attribute_Name
3928 (Attribute_Name
(Assoc_Node
)))
3931 P
:= Parent
(Assoc_Node
);
3933 -- Non-subexpression case. Note that N is initially Empty in this case
3934 -- (N is only guaranteed Non-Empty in the subexpr case).
3941 -- Capture root of the transient scope
3943 if Scope_Is_Transient
then
3944 Wrapped_Node
:= Node_To_Be_Wrapped
;
3948 pragma Assert
(Present
(P
));
3950 -- Make sure that inserted actions stay in the transient scope
3952 if Present
(Wrapped_Node
) and then N
= Wrapped_Node
then
3953 Store_Before_Actions_In_Scope
(Ins_Actions
);
3959 -- Case of right operand of AND THEN or OR ELSE. Put the actions
3960 -- in the Actions field of the right operand. They will be moved
3961 -- out further when the AND THEN or OR ELSE operator is expanded.
3962 -- Nothing special needs to be done for the left operand since
3963 -- in that case the actions are executed unconditionally.
3965 when N_Short_Circuit
=>
3966 if N
= Right_Opnd
(P
) then
3968 -- We are now going to either append the actions to the
3969 -- actions field of the short-circuit operation. We will
3970 -- also analyze the actions now.
3972 -- This analysis is really too early, the proper thing would
3973 -- be to just park them there now, and only analyze them if
3974 -- we find we really need them, and to it at the proper
3975 -- final insertion point. However attempting to this proved
3976 -- tricky, so for now we just kill current values before and
3977 -- after the analyze call to make sure we avoid peculiar
3978 -- optimizations from this out of order insertion.
3980 Kill_Current_Values
;
3982 -- If P has already been expanded, we can't park new actions
3983 -- on it, so we need to expand them immediately, introducing
3984 -- an Expression_With_Actions. N can't be an expression
3985 -- with actions, or else then the actions would have been
3986 -- inserted at an inner level.
3988 if Analyzed
(P
) then
3989 pragma Assert
(Nkind
(N
) /= N_Expression_With_Actions
);
3991 Make_Expression_With_Actions
(Sloc
(N
),
3992 Actions
=> Ins_Actions
,
3993 Expression
=> Relocate_Node
(N
)));
3994 Analyze_And_Resolve
(N
);
3996 elsif Present
(Actions
(P
)) then
3997 Insert_List_After_And_Analyze
3998 (Last
(Actions
(P
)), Ins_Actions
);
4000 Set_Actions
(P
, Ins_Actions
);
4001 Analyze_List
(Actions
(P
));
4004 Kill_Current_Values
;
4009 -- Then or Else dependent expression of an if expression. Add
4010 -- actions to Then_Actions or Else_Actions field as appropriate.
4011 -- The actions will be moved further out when the if is expanded.
4013 when N_If_Expression
=>
4015 ThenX
: constant Node_Id
:= Next
(First
(Expressions
(P
)));
4016 ElseX
: constant Node_Id
:= Next
(ThenX
);
4019 -- If the enclosing expression is already analyzed, as
4020 -- is the case for nested elaboration checks, insert the
4021 -- conditional further out.
4023 if Analyzed
(P
) then
4026 -- Actions belong to the then expression, temporarily place
4027 -- them as Then_Actions of the if expression. They will be
4028 -- moved to the proper place later when the if expression
4031 elsif N
= ThenX
then
4032 if Present
(Then_Actions
(P
)) then
4033 Insert_List_After_And_Analyze
4034 (Last
(Then_Actions
(P
)), Ins_Actions
);
4036 Set_Then_Actions
(P
, Ins_Actions
);
4037 Analyze_List
(Then_Actions
(P
));
4042 -- Actions belong to the else expression, temporarily place
4043 -- them as Else_Actions of the if expression. They will be
4044 -- moved to the proper place later when the if expression
4047 elsif N
= ElseX
then
4048 if Present
(Else_Actions
(P
)) then
4049 Insert_List_After_And_Analyze
4050 (Last
(Else_Actions
(P
)), Ins_Actions
);
4052 Set_Else_Actions
(P
, Ins_Actions
);
4053 Analyze_List
(Else_Actions
(P
));
4058 -- Actions belong to the condition. In this case they are
4059 -- unconditionally executed, and so we can continue the
4060 -- search for the proper insert point.
4067 -- Alternative of case expression, we place the action in the
4068 -- Actions field of the case expression alternative, this will
4069 -- be handled when the case expression is expanded.
4071 when N_Case_Expression_Alternative
=>
4072 if Present
(Actions
(P
)) then
4073 Insert_List_After_And_Analyze
4074 (Last
(Actions
(P
)), Ins_Actions
);
4076 Set_Actions
(P
, Ins_Actions
);
4077 Analyze_List
(Actions
(P
));
4082 -- Case of appearing within an Expressions_With_Actions node. When
4083 -- the new actions come from the expression of the expression with
4084 -- actions, they must be added to the existing actions. The other
4085 -- alternative is when the new actions are related to one of the
4086 -- existing actions of the expression with actions, and should
4087 -- never reach here: if actions are inserted on a statement
4088 -- within the Actions of an expression with actions, or on some
4089 -- sub-expression of such a statement, then the outermost proper
4090 -- insertion point is right before the statement, and we should
4091 -- never climb up as far as the N_Expression_With_Actions itself.
4093 when N_Expression_With_Actions
=>
4094 if N
= Expression
(P
) then
4095 if Is_Empty_List
(Actions
(P
)) then
4096 Append_List_To
(Actions
(P
), Ins_Actions
);
4097 Analyze_List
(Actions
(P
));
4099 Insert_List_After_And_Analyze
4100 (Last
(Actions
(P
)), Ins_Actions
);
4106 raise Program_Error
;
4109 -- Case of appearing in the condition of a while expression or
4110 -- elsif. We insert the actions into the Condition_Actions field.
4111 -- They will be moved further out when the while loop or elsif
4114 when N_Iteration_Scheme |
4117 if N
= Condition
(P
) then
4118 if Present
(Condition_Actions
(P
)) then
4119 Insert_List_After_And_Analyze
4120 (Last
(Condition_Actions
(P
)), Ins_Actions
);
4122 Set_Condition_Actions
(P
, Ins_Actions
);
4124 -- Set the parent of the insert actions explicitly. This
4125 -- is not a syntactic field, but we need the parent field
4126 -- set, in particular so that freeze can understand that
4127 -- it is dealing with condition actions, and properly
4128 -- insert the freezing actions.
4130 Set_Parent
(Ins_Actions
, P
);
4131 Analyze_List
(Condition_Actions
(P
));
4137 -- Statements, declarations, pragmas, representation clauses
4142 N_Procedure_Call_Statement |
4143 N_Statement_Other_Than_Procedure_Call |
4149 -- Representation_Clause
4152 N_Attribute_Definition_Clause |
4153 N_Enumeration_Representation_Clause |
4154 N_Record_Representation_Clause |
4158 N_Abstract_Subprogram_Declaration |
4160 N_Exception_Declaration |
4161 N_Exception_Renaming_Declaration |
4162 N_Expression_Function |
4163 N_Formal_Abstract_Subprogram_Declaration |
4164 N_Formal_Concrete_Subprogram_Declaration |
4165 N_Formal_Object_Declaration |
4166 N_Formal_Type_Declaration |
4167 N_Full_Type_Declaration |
4168 N_Function_Instantiation |
4169 N_Generic_Function_Renaming_Declaration |
4170 N_Generic_Package_Declaration |
4171 N_Generic_Package_Renaming_Declaration |
4172 N_Generic_Procedure_Renaming_Declaration |
4173 N_Generic_Subprogram_Declaration |
4174 N_Implicit_Label_Declaration |
4175 N_Incomplete_Type_Declaration |
4176 N_Number_Declaration |
4177 N_Object_Declaration |
4178 N_Object_Renaming_Declaration |
4180 N_Package_Body_Stub |
4181 N_Package_Declaration |
4182 N_Package_Instantiation |
4183 N_Package_Renaming_Declaration |
4184 N_Private_Extension_Declaration |
4185 N_Private_Type_Declaration |
4186 N_Procedure_Instantiation |
4188 N_Protected_Body_Stub |
4189 N_Protected_Type_Declaration |
4190 N_Single_Task_Declaration |
4192 N_Subprogram_Body_Stub |
4193 N_Subprogram_Declaration |
4194 N_Subprogram_Renaming_Declaration |
4195 N_Subtype_Declaration |
4198 N_Task_Type_Declaration |
4200 -- Use clauses can appear in lists of declarations
4202 N_Use_Package_Clause |
4205 -- Freeze entity behaves like a declaration or statement
4208 N_Freeze_Generic_Entity
4210 -- Do not insert here if the item is not a list member (this
4211 -- happens for example with a triggering statement, and the
4212 -- proper approach is to insert before the entire select).
4214 if not Is_List_Member
(P
) then
4217 -- Do not insert if parent of P is an N_Component_Association
4218 -- node (i.e. we are in the context of an N_Aggregate or
4219 -- N_Extension_Aggregate node. In this case we want to insert
4220 -- before the entire aggregate.
4222 elsif Nkind
(Parent
(P
)) = N_Component_Association
then
4225 -- Do not insert if the parent of P is either an N_Variant node
4226 -- or an N_Record_Definition node, meaning in either case that
4227 -- P is a member of a component list, and that therefore the
4228 -- actions should be inserted outside the complete record
4231 elsif Nkind_In
(Parent
(P
), N_Variant
, N_Record_Definition
) then
4234 -- Do not insert freeze nodes within the loop generated for
4235 -- an aggregate, because they may be elaborated too late for
4236 -- subsequent use in the back end: within a package spec the
4237 -- loop is part of the elaboration procedure and is only
4238 -- elaborated during the second pass.
4240 -- If the loop comes from source, or the entity is local to the
4241 -- loop itself it must remain within.
4243 elsif Nkind
(Parent
(P
)) = N_Loop_Statement
4244 and then not Comes_From_Source
(Parent
(P
))
4245 and then Nkind
(First
(Ins_Actions
)) = N_Freeze_Entity
4247 Scope
(Entity
(First
(Ins_Actions
))) /= Current_Scope
4251 -- Otherwise we can go ahead and do the insertion
4253 elsif P
= Wrapped_Node
then
4254 Store_Before_Actions_In_Scope
(Ins_Actions
);
4258 Insert_List_Before_And_Analyze
(P
, Ins_Actions
);
4262 -- A special case, N_Raise_xxx_Error can act either as a statement
4263 -- or a subexpression. We tell the difference by looking at the
4264 -- Etype. It is set to Standard_Void_Type in the statement case.
4267 N_Raise_xxx_Error
=>
4268 if Etype
(P
) = Standard_Void_Type
then
4269 if P
= Wrapped_Node
then
4270 Store_Before_Actions_In_Scope
(Ins_Actions
);
4272 Insert_List_Before_And_Analyze
(P
, Ins_Actions
);
4277 -- In the subexpression case, keep climbing
4283 -- If a component association appears within a loop created for
4284 -- an array aggregate, attach the actions to the association so
4285 -- they can be subsequently inserted within the loop. For other
4286 -- component associations insert outside of the aggregate. For
4287 -- an association that will generate a loop, its Loop_Actions
4288 -- attribute is already initialized (see exp_aggr.adb).
4290 -- The list of loop_actions can in turn generate additional ones,
4291 -- that are inserted before the associated node. If the associated
4292 -- node is outside the aggregate, the new actions are collected
4293 -- at the end of the loop actions, to respect the order in which
4294 -- they are to be elaborated.
4297 N_Component_Association
=>
4298 if Nkind
(Parent
(P
)) = N_Aggregate
4299 and then Present
(Loop_Actions
(P
))
4301 if Is_Empty_List
(Loop_Actions
(P
)) then
4302 Set_Loop_Actions
(P
, Ins_Actions
);
4303 Analyze_List
(Ins_Actions
);
4310 -- Check whether these actions were generated by a
4311 -- declaration that is part of the loop_ actions
4312 -- for the component_association.
4315 while Present
(Decl
) loop
4316 exit when Parent
(Decl
) = P
4317 and then Is_List_Member
(Decl
)
4319 List_Containing
(Decl
) = Loop_Actions
(P
);
4320 Decl
:= Parent
(Decl
);
4323 if Present
(Decl
) then
4324 Insert_List_Before_And_Analyze
4325 (Decl
, Ins_Actions
);
4327 Insert_List_After_And_Analyze
4328 (Last
(Loop_Actions
(P
)), Ins_Actions
);
4339 -- Another special case, an attribute denoting a procedure call
4342 N_Attribute_Reference
=>
4343 if Is_Procedure_Attribute_Name
(Attribute_Name
(P
)) then
4344 if P
= Wrapped_Node
then
4345 Store_Before_Actions_In_Scope
(Ins_Actions
);
4347 Insert_List_Before_And_Analyze
(P
, Ins_Actions
);
4352 -- In the subexpression case, keep climbing
4358 -- A contract node should not belong to the tree
4361 raise Program_Error
;
4363 -- For all other node types, keep climbing tree
4367 N_Accept_Alternative |
4368 N_Access_Definition |
4369 N_Access_Function_Definition |
4370 N_Access_Procedure_Definition |
4371 N_Access_To_Object_Definition |
4374 N_Aspect_Specification |
4376 N_Case_Statement_Alternative |
4377 N_Character_Literal |
4378 N_Compilation_Unit |
4379 N_Compilation_Unit_Aux |
4380 N_Component_Clause |
4381 N_Component_Declaration |
4382 N_Component_Definition |
4384 N_Constrained_Array_Definition |
4385 N_Decimal_Fixed_Point_Definition |
4386 N_Defining_Character_Literal |
4387 N_Defining_Identifier |
4388 N_Defining_Operator_Symbol |
4389 N_Defining_Program_Unit_Name |
4390 N_Delay_Alternative |
4391 N_Delta_Constraint |
4392 N_Derived_Type_Definition |
4394 N_Digits_Constraint |
4395 N_Discriminant_Association |
4396 N_Discriminant_Specification |
4398 N_Entry_Body_Formal_Part |
4399 N_Entry_Call_Alternative |
4400 N_Entry_Declaration |
4401 N_Entry_Index_Specification |
4402 N_Enumeration_Type_Definition |
4404 N_Exception_Handler |
4406 N_Explicit_Dereference |
4407 N_Extension_Aggregate |
4408 N_Floating_Point_Definition |
4409 N_Formal_Decimal_Fixed_Point_Definition |
4410 N_Formal_Derived_Type_Definition |
4411 N_Formal_Discrete_Type_Definition |
4412 N_Formal_Floating_Point_Definition |
4413 N_Formal_Modular_Type_Definition |
4414 N_Formal_Ordinary_Fixed_Point_Definition |
4415 N_Formal_Package_Declaration |
4416 N_Formal_Private_Type_Definition |
4417 N_Formal_Incomplete_Type_Definition |
4418 N_Formal_Signed_Integer_Type_Definition |
4420 N_Function_Specification |
4421 N_Generic_Association |
4422 N_Handled_Sequence_Of_Statements |
4425 N_Index_Or_Discriminant_Constraint |
4426 N_Indexed_Component |
4428 N_Iterator_Specification |
4431 N_Loop_Parameter_Specification |
4433 N_Modular_Type_Definition |
4459 N_Op_Shift_Right_Arithmetic |
4463 N_Ordinary_Fixed_Point_Definition |
4465 N_Package_Specification |
4466 N_Parameter_Association |
4467 N_Parameter_Specification |
4468 N_Pop_Constraint_Error_Label |
4469 N_Pop_Program_Error_Label |
4470 N_Pop_Storage_Error_Label |
4471 N_Pragma_Argument_Association |
4472 N_Procedure_Specification |
4473 N_Protected_Definition |
4474 N_Push_Constraint_Error_Label |
4475 N_Push_Program_Error_Label |
4476 N_Push_Storage_Error_Label |
4477 N_Qualified_Expression |
4478 N_Quantified_Expression |
4479 N_Raise_Expression |
4481 N_Range_Constraint |
4483 N_Real_Range_Specification |
4484 N_Record_Definition |
4486 N_SCIL_Dispatch_Table_Tag_Init |
4487 N_SCIL_Dispatching_Call |
4488 N_SCIL_Membership_Test |
4489 N_Selected_Component |
4490 N_Signed_Integer_Type_Definition |
4491 N_Single_Protected_Declaration |
4494 N_Subtype_Indication |
4497 N_Terminate_Alternative |
4498 N_Triggering_Alternative |
4500 N_Unchecked_Expression |
4501 N_Unchecked_Type_Conversion |
4502 N_Unconstrained_Array_Definition |
4507 N_Validate_Unchecked_Conversion |
4514 -- If we fall through above tests, keep climbing tree
4518 if Nkind
(Parent
(N
)) = N_Subunit
then
4520 -- This is the proper body corresponding to a stub. Insertion must
4521 -- be done at the point of the stub, which is in the declarative
4522 -- part of the parent unit.
4524 P
:= Corresponding_Stub
(Parent
(N
));
4532 -- Version with check(s) suppressed
4534 procedure Insert_Actions
4535 (Assoc_Node
: Node_Id
;
4536 Ins_Actions
: List_Id
;
4537 Suppress
: Check_Id
)
4540 if Suppress
= All_Checks
then
4542 Sva
: constant Suppress_Array
:= Scope_Suppress
.Suppress
;
4544 Scope_Suppress
.Suppress
:= (others => True);
4545 Insert_Actions
(Assoc_Node
, Ins_Actions
);
4546 Scope_Suppress
.Suppress
:= Sva
;
4551 Svg
: constant Boolean := Scope_Suppress
.Suppress
(Suppress
);
4553 Scope_Suppress
.Suppress
(Suppress
) := True;
4554 Insert_Actions
(Assoc_Node
, Ins_Actions
);
4555 Scope_Suppress
.Suppress
(Suppress
) := Svg
;
4560 --------------------------
4561 -- Insert_Actions_After --
4562 --------------------------
4564 procedure Insert_Actions_After
4565 (Assoc_Node
: Node_Id
;
4566 Ins_Actions
: List_Id
)
4569 if Scope_Is_Transient
and then Assoc_Node
= Node_To_Be_Wrapped
then
4570 Store_After_Actions_In_Scope
(Ins_Actions
);
4572 Insert_List_After_And_Analyze
(Assoc_Node
, Ins_Actions
);
4574 end Insert_Actions_After
;
4576 ------------------------
4577 -- Insert_Declaration --
4578 ------------------------
4580 procedure Insert_Declaration
(N
: Node_Id
; Decl
: Node_Id
) is
4584 pragma Assert
(Nkind
(N
) in N_Subexpr
);
4586 -- Climb until we find a procedure or a package
4590 pragma Assert
(Present
(Parent
(P
)));
4593 if Is_List_Member
(P
) then
4594 exit when Nkind_In
(Parent
(P
), N_Package_Specification
,
4597 -- Special handling for handled sequence of statements, we must
4598 -- insert in the statements not the exception handlers!
4600 if Nkind
(Parent
(P
)) = N_Handled_Sequence_Of_Statements
then
4601 P
:= First
(Statements
(Parent
(P
)));
4607 -- Now do the insertion
4609 Insert_Before
(P
, Decl
);
4611 end Insert_Declaration
;
4613 ---------------------------------
4614 -- Insert_Library_Level_Action --
4615 ---------------------------------
4617 procedure Insert_Library_Level_Action
(N
: Node_Id
) is
4618 Aux
: constant Node_Id
:= Aux_Decls_Node
(Cunit
(Main_Unit
));
4621 Push_Scope
(Cunit_Entity
(Main_Unit
));
4622 -- ??? should this be Current_Sem_Unit instead of Main_Unit?
4624 if No
(Actions
(Aux
)) then
4625 Set_Actions
(Aux
, New_List
(N
));
4627 Append
(N
, Actions
(Aux
));
4632 end Insert_Library_Level_Action
;
4634 ----------------------------------
4635 -- Insert_Library_Level_Actions --
4636 ----------------------------------
4638 procedure Insert_Library_Level_Actions
(L
: List_Id
) is
4639 Aux
: constant Node_Id
:= Aux_Decls_Node
(Cunit
(Main_Unit
));
4642 if Is_Non_Empty_List
(L
) then
4643 Push_Scope
(Cunit_Entity
(Main_Unit
));
4644 -- ??? should this be Current_Sem_Unit instead of Main_Unit?
4646 if No
(Actions
(Aux
)) then
4647 Set_Actions
(Aux
, L
);
4650 Insert_List_After_And_Analyze
(Last
(Actions
(Aux
)), L
);
4655 end Insert_Library_Level_Actions
;
4657 ----------------------
4658 -- Inside_Init_Proc --
4659 ----------------------
4661 function Inside_Init_Proc
return Boolean is
4666 while Present
(S
) and then S
/= Standard_Standard
loop
4667 if Is_Init_Proc
(S
) then
4675 end Inside_Init_Proc
;
4677 ----------------------------
4678 -- Is_All_Null_Statements --
4679 ----------------------------
4681 function Is_All_Null_Statements
(L
: List_Id
) return Boolean is
4686 while Present
(Stm
) loop
4687 if Nkind
(Stm
) /= N_Null_Statement
then
4695 end Is_All_Null_Statements
;
4697 --------------------------------------------------
4698 -- Is_Displacement_Of_Object_Or_Function_Result --
4699 --------------------------------------------------
4701 function Is_Displacement_Of_Object_Or_Function_Result
4702 (Obj_Id
: Entity_Id
) return Boolean
4704 function Is_Controlled_Function_Call
(N
: Node_Id
) return Boolean;
4705 -- Determine if particular node denotes a controlled function call. The
4706 -- call may have been heavily expanded.
4708 function Is_Displace_Call
(N
: Node_Id
) return Boolean;
4709 -- Determine whether a particular node is a call to Ada.Tags.Displace.
4710 -- The call might be nested within other actions such as conversions.
4712 function Is_Source_Object
(N
: Node_Id
) return Boolean;
4713 -- Determine whether a particular node denotes a source object
4715 ---------------------------------
4716 -- Is_Controlled_Function_Call --
4717 ---------------------------------
4719 function Is_Controlled_Function_Call
(N
: Node_Id
) return Boolean is
4720 Expr
: Node_Id
:= Original_Node
(N
);
4723 if Nkind
(Expr
) = N_Function_Call
then
4724 Expr
:= Name
(Expr
);
4726 -- When a function call appears in Object.Operation format, the
4727 -- original representation has two possible forms depending on the
4728 -- availability of actual parameters:
4730 -- Obj.Func_Call N_Selected_Component
4731 -- Obj.Func_Call (Param) N_Indexed_Component
4734 if Nkind
(Expr
) = N_Indexed_Component
then
4735 Expr
:= Prefix
(Expr
);
4738 if Nkind
(Expr
) = N_Selected_Component
then
4739 Expr
:= Selector_Name
(Expr
);
4744 Nkind_In
(Expr
, N_Expanded_Name
, N_Identifier
)
4745 and then Ekind
(Entity
(Expr
)) = E_Function
4746 and then Needs_Finalization
(Etype
(Entity
(Expr
)));
4747 end Is_Controlled_Function_Call
;
4749 ----------------------
4750 -- Is_Displace_Call --
4751 ----------------------
4753 function Is_Displace_Call
(N
: Node_Id
) return Boolean is
4754 Call
: Node_Id
:= N
;
4757 -- Strip various actions which may precede a call to Displace
4760 if Nkind
(Call
) = N_Explicit_Dereference
then
4761 Call
:= Prefix
(Call
);
4763 elsif Nkind_In
(Call
, N_Type_Conversion
,
4764 N_Unchecked_Type_Conversion
)
4766 Call
:= Expression
(Call
);
4775 and then Nkind
(Call
) = N_Function_Call
4776 and then Is_RTE
(Entity
(Name
(Call
)), RE_Displace
);
4777 end Is_Displace_Call
;
4779 ----------------------
4780 -- Is_Source_Object --
4781 ----------------------
4783 function Is_Source_Object
(N
: Node_Id
) return Boolean is
4787 and then Nkind
(N
) in N_Has_Entity
4788 and then Is_Object
(Entity
(N
))
4789 and then Comes_From_Source
(N
);
4790 end Is_Source_Object
;
4794 Decl
: constant Node_Id
:= Parent
(Obj_Id
);
4795 Obj_Typ
: constant Entity_Id
:= Base_Type
(Etype
(Obj_Id
));
4796 Orig_Decl
: constant Node_Id
:= Original_Node
(Decl
);
4798 -- Start of processing for Is_Displacement_Of_Object_Or_Function_Result
4803 -- Obj : CW_Type := Function_Call (...);
4807 -- Tmp : ... := Function_Call (...)'reference;
4808 -- Obj : CW_Type renames (... Ada.Tags.Displace (Tmp));
4810 -- where the return type of the function and the class-wide type require
4811 -- dispatch table pointer displacement.
4815 -- Obj : CW_Type := Src_Obj;
4819 -- Obj : CW_Type renames (... Ada.Tags.Displace (Src_Obj));
4821 -- where the type of the source object and the class-wide type require
4822 -- dispatch table pointer displacement.
4825 Nkind
(Decl
) = N_Object_Renaming_Declaration
4826 and then Nkind
(Orig_Decl
) = N_Object_Declaration
4827 and then Comes_From_Source
(Orig_Decl
)
4828 and then Is_Class_Wide_Type
(Obj_Typ
)
4829 and then Is_Displace_Call
(Renamed_Object
(Obj_Id
))
4831 (Is_Controlled_Function_Call
(Expression
(Orig_Decl
))
4832 or else Is_Source_Object
(Expression
(Orig_Decl
)));
4833 end Is_Displacement_Of_Object_Or_Function_Result
;
4835 ------------------------------
4836 -- Is_Finalizable_Transient --
4837 ------------------------------
4839 function Is_Finalizable_Transient
4841 Rel_Node
: Node_Id
) return Boolean
4843 Obj_Id
: constant Entity_Id
:= Defining_Identifier
(Decl
);
4844 Obj_Typ
: constant Entity_Id
:= Base_Type
(Etype
(Obj_Id
));
4846 function Initialized_By_Access
(Trans_Id
: Entity_Id
) return Boolean;
4847 -- Determine whether transient object Trans_Id is initialized either
4848 -- by a function call which returns an access type or simply renames
4851 function Initialized_By_Aliased_BIP_Func_Call
4852 (Trans_Id
: Entity_Id
) return Boolean;
4853 -- Determine whether transient object Trans_Id is initialized by a
4854 -- build-in-place function call where the BIPalloc parameter is of
4855 -- value 1 and BIPaccess is not null. This case creates an aliasing
4856 -- between the returned value and the value denoted by BIPaccess.
4859 (Trans_Id
: Entity_Id
;
4860 First_Stmt
: Node_Id
) return Boolean;
4861 -- Determine whether transient object Trans_Id has been renamed or
4862 -- aliased through 'reference in the statement list starting from
4865 function Is_Allocated
(Trans_Id
: Entity_Id
) return Boolean;
4866 -- Determine whether transient object Trans_Id is allocated on the heap
4868 function Is_Iterated_Container
4869 (Trans_Id
: Entity_Id
;
4870 First_Stmt
: Node_Id
) return Boolean;
4871 -- Determine whether transient object Trans_Id denotes a container which
4872 -- is in the process of being iterated in the statement list starting
4875 ---------------------------
4876 -- Initialized_By_Access --
4877 ---------------------------
4879 function Initialized_By_Access
(Trans_Id
: Entity_Id
) return Boolean is
4880 Expr
: constant Node_Id
:= Expression
(Parent
(Trans_Id
));
4885 and then Nkind
(Expr
) /= N_Reference
4886 and then Is_Access_Type
(Etype
(Expr
));
4887 end Initialized_By_Access
;
4889 ------------------------------------------
4890 -- Initialized_By_Aliased_BIP_Func_Call --
4891 ------------------------------------------
4893 function Initialized_By_Aliased_BIP_Func_Call
4894 (Trans_Id
: Entity_Id
) return Boolean
4896 Call
: Node_Id
:= Expression
(Parent
(Trans_Id
));
4899 -- Build-in-place calls usually appear in 'reference format
4901 if Nkind
(Call
) = N_Reference
then
4902 Call
:= Prefix
(Call
);
4905 if Is_Build_In_Place_Function_Call
(Call
) then
4907 Access_Nam
: Name_Id
:= No_Name
;
4908 Access_OK
: Boolean := False;
4910 Alloc_Nam
: Name_Id
:= No_Name
;
4911 Alloc_OK
: Boolean := False;
4913 Func_Id
: Entity_Id
;
4917 -- Examine all parameter associations of the function call
4919 Param
:= First
(Parameter_Associations
(Call
));
4920 while Present
(Param
) loop
4921 if Nkind
(Param
) = N_Parameter_Association
4922 and then Nkind
(Selector_Name
(Param
)) = N_Identifier
4924 Actual
:= Explicit_Actual_Parameter
(Param
);
4925 Formal
:= Selector_Name
(Param
);
4927 -- Construct the names of formals BIPaccess and BIPalloc
4928 -- using the function name retrieved from an arbitrary
4931 if Access_Nam
= No_Name
4932 and then Alloc_Nam
= No_Name
4933 and then Present
(Entity
(Formal
))
4935 Func_Id
:= Scope
(Entity
(Formal
));
4938 New_External_Name
(Chars
(Func_Id
),
4939 BIP_Formal_Suffix
(BIP_Object_Access
));
4942 New_External_Name
(Chars
(Func_Id
),
4943 BIP_Formal_Suffix
(BIP_Alloc_Form
));
4946 -- A match for BIPaccess => Temp has been found
4948 if Chars
(Formal
) = Access_Nam
4949 and then Nkind
(Actual
) /= N_Null
4954 -- A match for BIPalloc => 1 has been found
4956 if Chars
(Formal
) = Alloc_Nam
4957 and then Nkind
(Actual
) = N_Integer_Literal
4958 and then Intval
(Actual
) = Uint_1
4967 return Access_OK
and Alloc_OK
;
4972 end Initialized_By_Aliased_BIP_Func_Call
;
4979 (Trans_Id
: Entity_Id
;
4980 First_Stmt
: Node_Id
) return Boolean
4982 function Find_Renamed_Object
(Ren_Decl
: Node_Id
) return Entity_Id
;
4983 -- Given an object renaming declaration, retrieve the entity of the
4984 -- renamed name. Return Empty if the renamed name is anything other
4985 -- than a variable or a constant.
4987 -------------------------
4988 -- Find_Renamed_Object --
4989 -------------------------
4991 function Find_Renamed_Object
(Ren_Decl
: Node_Id
) return Entity_Id
is
4992 Ren_Obj
: Node_Id
:= Empty
;
4994 function Find_Object
(N
: Node_Id
) return Traverse_Result
;
4995 -- Try to detect an object which is either a constant or a
5002 function Find_Object
(N
: Node_Id
) return Traverse_Result
is
5004 -- Stop the search once a constant or a variable has been
5007 if Nkind
(N
) = N_Identifier
5008 and then Present
(Entity
(N
))
5009 and then Ekind_In
(Entity
(N
), E_Constant
, E_Variable
)
5011 Ren_Obj
:= Entity
(N
);
5018 procedure Search
is new Traverse_Proc
(Find_Object
);
5022 Typ
: constant Entity_Id
:= Etype
(Defining_Identifier
(Ren_Decl
));
5024 -- Start of processing for Find_Renamed_Object
5027 -- Actions related to dispatching calls may appear as renamings of
5028 -- tags. Do not process this type of renaming because it does not
5029 -- use the actual value of the object.
5031 if not Is_RTE
(Typ
, RE_Tag_Ptr
) then
5032 Search
(Name
(Ren_Decl
));
5036 end Find_Renamed_Object
;
5041 Ren_Obj
: Entity_Id
;
5044 -- Start of processing for Is_Aliased
5047 -- A controlled transient object is not considered aliased when it
5048 -- appears inside an expression_with_actions node even when there are
5049 -- explicit aliases of it:
5052 -- Trans_Id : Ctrl_Typ ...; -- controlled transient object
5053 -- Alias : ... := Trans_Id; -- object is aliased
5054 -- Val : constant Boolean :=
5055 -- ... Alias ...; -- aliasing ends
5056 -- <finalize Trans_Id> -- object safe to finalize
5059 -- Expansion ensures that all aliases are encapsulated in the actions
5060 -- list and do not leak to the expression by forcing the evaluation
5061 -- of the expression.
5063 if Nkind
(Rel_Node
) = N_Expression_With_Actions
then
5066 -- Otherwise examine the statements after the controlled transient
5067 -- object and look for various forms of aliasing.
5071 while Present
(Stmt
) loop
5072 if Nkind
(Stmt
) = N_Object_Declaration
then
5073 Expr
:= Expression
(Stmt
);
5075 -- Aliasing of the form:
5076 -- Obj : ... := Trans_Id'reference;
5079 and then Nkind
(Expr
) = N_Reference
5080 and then Nkind
(Prefix
(Expr
)) = N_Identifier
5081 and then Entity
(Prefix
(Expr
)) = Trans_Id
5086 elsif Nkind
(Stmt
) = N_Object_Renaming_Declaration
then
5087 Ren_Obj
:= Find_Renamed_Object
(Stmt
);
5089 -- Aliasing of the form:
5090 -- Obj : ... renames ... Trans_Id ...;
5092 if Present
(Ren_Obj
) and then Ren_Obj
= Trans_Id
then
5108 function Is_Allocated
(Trans_Id
: Entity_Id
) return Boolean is
5109 Expr
: constant Node_Id
:= Expression
(Parent
(Trans_Id
));
5112 Is_Access_Type
(Etype
(Trans_Id
))
5113 and then Present
(Expr
)
5114 and then Nkind
(Expr
) = N_Allocator
;
5117 ---------------------------
5118 -- Is_Iterated_Container --
5119 ---------------------------
5121 function Is_Iterated_Container
5122 (Trans_Id
: Entity_Id
;
5123 First_Stmt
: Node_Id
) return Boolean
5133 -- It is not possible to iterate over containers in non-Ada 2012 code
5135 if Ada_Version
< Ada_2012
then
5139 Typ
:= Etype
(Trans_Id
);
5141 -- Handle access type created for secondary stack use
5143 if Is_Access_Type
(Typ
) then
5144 Typ
:= Designated_Type
(Typ
);
5147 -- Look for aspect Default_Iterator. It may be part of a type
5148 -- declaration for a container, or inherited from a base type
5151 Aspect
:= Find_Value_Of_Aspect
(Typ
, Aspect_Default_Iterator
);
5153 if Present
(Aspect
) then
5154 Iter
:= Entity
(Aspect
);
5156 -- Examine the statements following the container object and
5157 -- look for a call to the default iterate routine where the
5158 -- first parameter is the transient. Such a call appears as:
5160 -- It : Access_To_CW_Iterator :=
5161 -- Iterate (Tran_Id.all, ...)'reference;
5164 while Present
(Stmt
) loop
5166 -- Detect an object declaration which is initialized by a
5167 -- secondary stack function call.
5169 if Nkind
(Stmt
) = N_Object_Declaration
5170 and then Present
(Expression
(Stmt
))
5171 and then Nkind
(Expression
(Stmt
)) = N_Reference
5172 and then Nkind
(Prefix
(Expression
(Stmt
))) = N_Function_Call
5174 Call
:= Prefix
(Expression
(Stmt
));
5176 -- The call must invoke the default iterate routine of
5177 -- the container and the transient object must appear as
5178 -- the first actual parameter. Skip any calls whose names
5179 -- are not entities.
5181 if Is_Entity_Name
(Name
(Call
))
5182 and then Entity
(Name
(Call
)) = Iter
5183 and then Present
(Parameter_Associations
(Call
))
5185 Param
:= First
(Parameter_Associations
(Call
));
5187 if Nkind
(Param
) = N_Explicit_Dereference
5188 and then Entity
(Prefix
(Param
)) = Trans_Id
5200 end Is_Iterated_Container
;
5204 Desig
: Entity_Id
:= Obj_Typ
;
5206 -- Start of processing for Is_Finalizable_Transient
5209 -- Handle access types
5211 if Is_Access_Type
(Desig
) then
5212 Desig
:= Available_View
(Designated_Type
(Desig
));
5216 Ekind_In
(Obj_Id
, E_Constant
, E_Variable
)
5217 and then Needs_Finalization
(Desig
)
5218 and then Requires_Transient_Scope
(Desig
)
5219 and then Nkind
(Rel_Node
) /= N_Simple_Return_Statement
5221 -- Do not consider renamed or 'reference-d transient objects because
5222 -- the act of renaming extends the object's lifetime.
5224 and then not Is_Aliased
(Obj_Id
, Decl
)
5226 -- Do not consider transient objects allocated on the heap since
5227 -- they are attached to a finalization master.
5229 and then not Is_Allocated
(Obj_Id
)
5231 -- If the transient object is a pointer, check that it is not
5232 -- initialized by a function that returns a pointer or acts as a
5233 -- renaming of another pointer.
5236 (not Is_Access_Type
(Obj_Typ
)
5237 or else not Initialized_By_Access
(Obj_Id
))
5239 -- Do not consider transient objects which act as indirect aliases
5240 -- of build-in-place function results.
5242 and then not Initialized_By_Aliased_BIP_Func_Call
(Obj_Id
)
5244 -- Do not consider conversions of tags to class-wide types
5246 and then not Is_Tag_To_Class_Wide_Conversion
(Obj_Id
)
5248 -- Do not consider iterators because those are treated as normal
5249 -- controlled objects and are processed by the usual finalization
5250 -- machinery. This avoids the double finalization of an iterator.
5252 and then not Is_Iterator
(Desig
)
5254 -- Do not consider containers in the context of iterator loops. Such
5255 -- transient objects must exist for as long as the loop is around,
5256 -- otherwise any operation carried out by the iterator will fail.
5258 and then not Is_Iterated_Container
(Obj_Id
, Decl
);
5259 end Is_Finalizable_Transient
;
5261 ---------------------------------
5262 -- Is_Fully_Repped_Tagged_Type --
5263 ---------------------------------
5265 function Is_Fully_Repped_Tagged_Type
(T
: Entity_Id
) return Boolean is
5266 U
: constant Entity_Id
:= Underlying_Type
(T
);
5270 if No
(U
) or else not Is_Tagged_Type
(U
) then
5272 elsif Has_Discriminants
(U
) then
5274 elsif not Has_Specified_Layout
(U
) then
5278 -- Here we have a tagged type, see if it has any unlayed out fields
5279 -- other than a possible tag and parent fields. If so, we return False.
5281 Comp
:= First_Component
(U
);
5282 while Present
(Comp
) loop
5283 if not Is_Tag
(Comp
)
5284 and then Chars
(Comp
) /= Name_uParent
5285 and then No
(Component_Clause
(Comp
))
5289 Next_Component
(Comp
);
5293 -- All components are layed out
5296 end Is_Fully_Repped_Tagged_Type
;
5298 ----------------------------------
5299 -- Is_Library_Level_Tagged_Type --
5300 ----------------------------------
5302 function Is_Library_Level_Tagged_Type
(Typ
: Entity_Id
) return Boolean is
5304 return Is_Tagged_Type
(Typ
) and then Is_Library_Level_Entity
(Typ
);
5305 end Is_Library_Level_Tagged_Type
;
5307 --------------------------
5308 -- Is_Non_BIP_Func_Call --
5309 --------------------------
5311 function Is_Non_BIP_Func_Call
(Expr
: Node_Id
) return Boolean is
5313 -- The expected call is of the format
5315 -- Func_Call'reference
5318 Nkind
(Expr
) = N_Reference
5319 and then Nkind
(Prefix
(Expr
)) = N_Function_Call
5320 and then not Is_Build_In_Place_Function_Call
(Prefix
(Expr
));
5321 end Is_Non_BIP_Func_Call
;
5323 ------------------------------------
5324 -- Is_Object_Access_BIP_Func_Call --
5325 ------------------------------------
5327 function Is_Object_Access_BIP_Func_Call
5329 Obj_Id
: Entity_Id
) return Boolean
5331 Access_Nam
: Name_Id
:= No_Name
;
5338 -- Build-in-place calls usually appear in 'reference format. Note that
5339 -- the accessibility check machinery may add an extra 'reference due to
5340 -- side effect removal.
5343 while Nkind
(Call
) = N_Reference
loop
5344 Call
:= Prefix
(Call
);
5347 if Nkind_In
(Call
, N_Qualified_Expression
,
5348 N_Unchecked_Type_Conversion
)
5350 Call
:= Expression
(Call
);
5353 if Is_Build_In_Place_Function_Call
(Call
) then
5355 -- Examine all parameter associations of the function call
5357 Param
:= First
(Parameter_Associations
(Call
));
5358 while Present
(Param
) loop
5359 if Nkind
(Param
) = N_Parameter_Association
5360 and then Nkind
(Selector_Name
(Param
)) = N_Identifier
5362 Formal
:= Selector_Name
(Param
);
5363 Actual
:= Explicit_Actual_Parameter
(Param
);
5365 -- Construct the name of formal BIPaccess. It is much easier to
5366 -- extract the name of the function using an arbitrary formal's
5367 -- scope rather than the Name field of Call.
5369 if Access_Nam
= No_Name
and then Present
(Entity
(Formal
)) then
5372 (Chars
(Scope
(Entity
(Formal
))),
5373 BIP_Formal_Suffix
(BIP_Object_Access
));
5376 -- A match for BIPaccess => Obj_Id'Unrestricted_Access has been
5379 if Chars
(Formal
) = Access_Nam
5380 and then Nkind
(Actual
) = N_Attribute_Reference
5381 and then Attribute_Name
(Actual
) = Name_Unrestricted_Access
5382 and then Nkind
(Prefix
(Actual
)) = N_Identifier
5383 and then Entity
(Prefix
(Actual
)) = Obj_Id
5394 end Is_Object_Access_BIP_Func_Call
;
5396 ----------------------------------
5397 -- Is_Possibly_Unaligned_Object --
5398 ----------------------------------
5400 function Is_Possibly_Unaligned_Object
(N
: Node_Id
) return Boolean is
5401 T
: constant Entity_Id
:= Etype
(N
);
5404 -- If renamed object, apply test to underlying object
5406 if Is_Entity_Name
(N
)
5407 and then Is_Object
(Entity
(N
))
5408 and then Present
(Renamed_Object
(Entity
(N
)))
5410 return Is_Possibly_Unaligned_Object
(Renamed_Object
(Entity
(N
)));
5413 -- Tagged and controlled types and aliased types are always aligned, as
5414 -- are concurrent types.
5417 or else Has_Controlled_Component
(T
)
5418 or else Is_Concurrent_Type
(T
)
5419 or else Is_Tagged_Type
(T
)
5420 or else Is_Controlled
(T
)
5425 -- If this is an element of a packed array, may be unaligned
5427 if Is_Ref_To_Bit_Packed_Array
(N
) then
5431 -- Case of indexed component reference: test whether prefix is unaligned
5433 if Nkind
(N
) = N_Indexed_Component
then
5434 return Is_Possibly_Unaligned_Object
(Prefix
(N
));
5436 -- Case of selected component reference
5438 elsif Nkind
(N
) = N_Selected_Component
then
5440 P
: constant Node_Id
:= Prefix
(N
);
5441 C
: constant Entity_Id
:= Entity
(Selector_Name
(N
));
5446 -- If component reference is for an array with non-static bounds,
5447 -- then it is always aligned: we can only process unaligned arrays
5448 -- with static bounds (more precisely compile time known bounds).
5450 if Is_Array_Type
(T
)
5451 and then not Compile_Time_Known_Bounds
(T
)
5456 -- If component is aliased, it is definitely properly aligned
5458 if Is_Aliased
(C
) then
5462 -- If component is for a type implemented as a scalar, and the
5463 -- record is packed, and the component is other than the first
5464 -- component of the record, then the component may be unaligned.
5466 if Is_Packed
(Etype
(P
))
5467 and then Represented_As_Scalar
(Etype
(C
))
5468 and then First_Entity
(Scope
(C
)) /= C
5473 -- Compute maximum possible alignment for T
5475 -- If alignment is known, then that settles things
5477 if Known_Alignment
(T
) then
5478 M
:= UI_To_Int
(Alignment
(T
));
5480 -- If alignment is not known, tentatively set max alignment
5483 M
:= Ttypes
.Maximum_Alignment
;
5485 -- We can reduce this if the Esize is known since the default
5486 -- alignment will never be more than the smallest power of 2
5487 -- that does not exceed this Esize value.
5489 if Known_Esize
(T
) then
5490 S
:= UI_To_Int
(Esize
(T
));
5492 while (M
/ 2) >= S
loop
5498 -- The following code is historical, it used to be present but it
5499 -- is too cautious, because the front-end does not know the proper
5500 -- default alignments for the target. Also, if the alignment is
5501 -- not known, the front end can't know in any case. If a copy is
5502 -- needed, the back-end will take care of it. This whole section
5503 -- including this comment can be removed later ???
5505 -- If the component reference is for a record that has a specified
5506 -- alignment, and we either know it is too small, or cannot tell,
5507 -- then the component may be unaligned.
5509 -- What is the following commented out code ???
5511 -- if Known_Alignment (Etype (P))
5512 -- and then Alignment (Etype (P)) < Ttypes.Maximum_Alignment
5513 -- and then M > Alignment (Etype (P))
5518 -- Case of component clause present which may specify an
5519 -- unaligned position.
5521 if Present
(Component_Clause
(C
)) then
5523 -- Otherwise we can do a test to make sure that the actual
5524 -- start position in the record, and the length, are both
5525 -- consistent with the required alignment. If not, we know
5526 -- that we are unaligned.
5529 Align_In_Bits
: constant Nat
:= M
* System_Storage_Unit
;
5531 if Component_Bit_Offset
(C
) mod Align_In_Bits
/= 0
5532 or else Esize
(C
) mod Align_In_Bits
/= 0
5539 -- Otherwise, for a component reference, test prefix
5541 return Is_Possibly_Unaligned_Object
(P
);
5544 -- If not a component reference, must be aligned
5549 end Is_Possibly_Unaligned_Object
;
5551 ---------------------------------
5552 -- Is_Possibly_Unaligned_Slice --
5553 ---------------------------------
5555 function Is_Possibly_Unaligned_Slice
(N
: Node_Id
) return Boolean is
5557 -- Go to renamed object
5559 if Is_Entity_Name
(N
)
5560 and then Is_Object
(Entity
(N
))
5561 and then Present
(Renamed_Object
(Entity
(N
)))
5563 return Is_Possibly_Unaligned_Slice
(Renamed_Object
(Entity
(N
)));
5566 -- The reference must be a slice
5568 if Nkind
(N
) /= N_Slice
then
5572 -- We only need to worry if the target has strict alignment
5574 if not Target_Strict_Alignment
then
5578 -- If it is a slice, then look at the array type being sliced
5581 Sarr
: constant Node_Id
:= Prefix
(N
);
5582 -- Prefix of the slice, i.e. the array being sliced
5584 Styp
: constant Entity_Id
:= Etype
(Prefix
(N
));
5585 -- Type of the array being sliced
5591 -- The problems arise if the array object that is being sliced
5592 -- is a component of a record or array, and we cannot guarantee
5593 -- the alignment of the array within its containing object.
5595 -- To investigate this, we look at successive prefixes to see
5596 -- if we have a worrisome indexed or selected component.
5600 -- Case of array is part of an indexed component reference
5602 if Nkind
(Pref
) = N_Indexed_Component
then
5603 Ptyp
:= Etype
(Prefix
(Pref
));
5605 -- The only problematic case is when the array is packed, in
5606 -- which case we really know nothing about the alignment of
5607 -- individual components.
5609 if Is_Bit_Packed_Array
(Ptyp
) then
5613 -- Case of array is part of a selected component reference
5615 elsif Nkind
(Pref
) = N_Selected_Component
then
5616 Ptyp
:= Etype
(Prefix
(Pref
));
5618 -- We are definitely in trouble if the record in question
5619 -- has an alignment, and either we know this alignment is
5620 -- inconsistent with the alignment of the slice, or we don't
5621 -- know what the alignment of the slice should be.
5623 if Known_Alignment
(Ptyp
)
5624 and then (Unknown_Alignment
(Styp
)
5625 or else Alignment
(Styp
) > Alignment
(Ptyp
))
5630 -- We are in potential trouble if the record type is packed.
5631 -- We could special case when we know that the array is the
5632 -- first component, but that's not such a simple case ???
5634 if Is_Packed
(Ptyp
) then
5638 -- We are in trouble if there is a component clause, and
5639 -- either we do not know the alignment of the slice, or
5640 -- the alignment of the slice is inconsistent with the
5641 -- bit position specified by the component clause.
5644 Field
: constant Entity_Id
:= Entity
(Selector_Name
(Pref
));
5646 if Present
(Component_Clause
(Field
))
5648 (Unknown_Alignment
(Styp
)
5650 (Component_Bit_Offset
(Field
) mod
5651 (System_Storage_Unit
* Alignment
(Styp
))) /= 0)
5657 -- For cases other than selected or indexed components we know we
5658 -- are OK, since no issues arise over alignment.
5664 -- We processed an indexed component or selected component
5665 -- reference that looked safe, so keep checking prefixes.
5667 Pref
:= Prefix
(Pref
);
5670 end Is_Possibly_Unaligned_Slice
;
5672 -------------------------------
5673 -- Is_Related_To_Func_Return --
5674 -------------------------------
5676 function Is_Related_To_Func_Return
(Id
: Entity_Id
) return Boolean is
5677 Expr
: constant Node_Id
:= Related_Expression
(Id
);
5681 and then Nkind
(Expr
) = N_Explicit_Dereference
5682 and then Nkind
(Parent
(Expr
)) = N_Simple_Return_Statement
;
5683 end Is_Related_To_Func_Return
;
5685 --------------------------------
5686 -- Is_Ref_To_Bit_Packed_Array --
5687 --------------------------------
5689 function Is_Ref_To_Bit_Packed_Array
(N
: Node_Id
) return Boolean is
5694 if Is_Entity_Name
(N
)
5695 and then Is_Object
(Entity
(N
))
5696 and then Present
(Renamed_Object
(Entity
(N
)))
5698 return Is_Ref_To_Bit_Packed_Array
(Renamed_Object
(Entity
(N
)));
5701 if Nkind_In
(N
, N_Indexed_Component
, N_Selected_Component
) then
5702 if Is_Bit_Packed_Array
(Etype
(Prefix
(N
))) then
5705 Result
:= Is_Ref_To_Bit_Packed_Array
(Prefix
(N
));
5708 if Result
and then Nkind
(N
) = N_Indexed_Component
then
5709 Expr
:= First
(Expressions
(N
));
5710 while Present
(Expr
) loop
5711 Force_Evaluation
(Expr
);
5721 end Is_Ref_To_Bit_Packed_Array
;
5723 --------------------------------
5724 -- Is_Ref_To_Bit_Packed_Slice --
5725 --------------------------------
5727 function Is_Ref_To_Bit_Packed_Slice
(N
: Node_Id
) return Boolean is
5729 if Nkind
(N
) = N_Type_Conversion
then
5730 return Is_Ref_To_Bit_Packed_Slice
(Expression
(N
));
5732 elsif Is_Entity_Name
(N
)
5733 and then Is_Object
(Entity
(N
))
5734 and then Present
(Renamed_Object
(Entity
(N
)))
5736 return Is_Ref_To_Bit_Packed_Slice
(Renamed_Object
(Entity
(N
)));
5738 elsif Nkind
(N
) = N_Slice
5739 and then Is_Bit_Packed_Array
(Etype
(Prefix
(N
)))
5743 elsif Nkind_In
(N
, N_Indexed_Component
, N_Selected_Component
) then
5744 return Is_Ref_To_Bit_Packed_Slice
(Prefix
(N
));
5749 end Is_Ref_To_Bit_Packed_Slice
;
5751 -----------------------
5752 -- Is_Renamed_Object --
5753 -----------------------
5755 function Is_Renamed_Object
(N
: Node_Id
) return Boolean is
5756 Pnod
: constant Node_Id
:= Parent
(N
);
5757 Kind
: constant Node_Kind
:= Nkind
(Pnod
);
5759 if Kind
= N_Object_Renaming_Declaration
then
5761 elsif Nkind_In
(Kind
, N_Indexed_Component
, N_Selected_Component
) then
5762 return Is_Renamed_Object
(Pnod
);
5766 end Is_Renamed_Object
;
5768 --------------------------------------
5769 -- Is_Secondary_Stack_BIP_Func_Call --
5770 --------------------------------------
5772 function Is_Secondary_Stack_BIP_Func_Call
(Expr
: Node_Id
) return Boolean is
5773 Alloc_Nam
: Name_Id
:= No_Name
;
5775 Call
: Node_Id
:= Expr
;
5780 -- Build-in-place calls usually appear in 'reference format. Note that
5781 -- the accessibility check machinery may add an extra 'reference due to
5782 -- side effect removal.
5784 while Nkind
(Call
) = N_Reference
loop
5785 Call
:= Prefix
(Call
);
5788 if Nkind_In
(Call
, N_Qualified_Expression
,
5789 N_Unchecked_Type_Conversion
)
5791 Call
:= Expression
(Call
);
5794 if Is_Build_In_Place_Function_Call
(Call
) then
5796 -- Examine all parameter associations of the function call
5798 Param
:= First
(Parameter_Associations
(Call
));
5799 while Present
(Param
) loop
5800 if Nkind
(Param
) = N_Parameter_Association
5801 and then Nkind
(Selector_Name
(Param
)) = N_Identifier
5803 Formal
:= Selector_Name
(Param
);
5804 Actual
:= Explicit_Actual_Parameter
(Param
);
5806 -- Construct the name of formal BIPalloc. It is much easier to
5807 -- extract the name of the function using an arbitrary formal's
5808 -- scope rather than the Name field of Call.
5810 if Alloc_Nam
= No_Name
and then Present
(Entity
(Formal
)) then
5813 (Chars
(Scope
(Entity
(Formal
))),
5814 BIP_Formal_Suffix
(BIP_Alloc_Form
));
5817 -- A match for BIPalloc => 2 has been found
5819 if Chars
(Formal
) = Alloc_Nam
5820 and then Nkind
(Actual
) = N_Integer_Literal
5821 and then Intval
(Actual
) = Uint_2
5832 end Is_Secondary_Stack_BIP_Func_Call
;
5834 -------------------------------------
5835 -- Is_Tag_To_Class_Wide_Conversion --
5836 -------------------------------------
5838 function Is_Tag_To_Class_Wide_Conversion
5839 (Obj_Id
: Entity_Id
) return Boolean
5841 Expr
: constant Node_Id
:= Expression
(Parent
(Obj_Id
));
5845 Is_Class_Wide_Type
(Etype
(Obj_Id
))
5846 and then Present
(Expr
)
5847 and then Nkind
(Expr
) = N_Unchecked_Type_Conversion
5848 and then Etype
(Expression
(Expr
)) = RTE
(RE_Tag
);
5849 end Is_Tag_To_Class_Wide_Conversion
;
5851 ----------------------------
5852 -- Is_Untagged_Derivation --
5853 ----------------------------
5855 function Is_Untagged_Derivation
(T
: Entity_Id
) return Boolean is
5857 return (not Is_Tagged_Type
(T
) and then Is_Derived_Type
(T
))
5859 (Is_Private_Type
(T
) and then Present
(Full_View
(T
))
5860 and then not Is_Tagged_Type
(Full_View
(T
))
5861 and then Is_Derived_Type
(Full_View
(T
))
5862 and then Etype
(Full_View
(T
)) /= T
);
5863 end Is_Untagged_Derivation
;
5865 ---------------------------
5866 -- Is_Volatile_Reference --
5867 ---------------------------
5869 function Is_Volatile_Reference
(N
: Node_Id
) return Boolean is
5871 -- Only source references are to be treated as volatile, internally
5872 -- generated stuff cannot have volatile external effects.
5874 if not Comes_From_Source
(N
) then
5877 -- Never true for reference to a type
5879 elsif Is_Entity_Name
(N
) and then Is_Type
(Entity
(N
)) then
5882 -- Never true for a compile time known constant
5884 elsif Compile_Time_Known_Value
(N
) then
5887 -- True if object reference with volatile type
5889 elsif Is_Volatile_Object
(N
) then
5892 -- True if reference to volatile entity
5894 elsif Is_Entity_Name
(N
) then
5895 return Treat_As_Volatile
(Entity
(N
));
5897 -- True for slice of volatile array
5899 elsif Nkind
(N
) = N_Slice
then
5900 return Is_Volatile_Reference
(Prefix
(N
));
5902 -- True if volatile component
5904 elsif Nkind_In
(N
, N_Indexed_Component
, N_Selected_Component
) then
5905 if (Is_Entity_Name
(Prefix
(N
))
5906 and then Has_Volatile_Components
(Entity
(Prefix
(N
))))
5907 or else (Present
(Etype
(Prefix
(N
)))
5908 and then Has_Volatile_Components
(Etype
(Prefix
(N
))))
5912 return Is_Volatile_Reference
(Prefix
(N
));
5920 end Is_Volatile_Reference
;
5922 --------------------
5923 -- Kill_Dead_Code --
5924 --------------------
5926 procedure Kill_Dead_Code
(N
: Node_Id
; Warn
: Boolean := False) is
5927 W
: Boolean := Warn
;
5928 -- Set False if warnings suppressed
5932 Remove_Warning_Messages
(N
);
5934 -- Generate warning if appropriate
5938 -- We suppress the warning if this code is under control of an
5939 -- if statement, whose condition is a simple identifier, and
5940 -- either we are in an instance, or warnings off is set for this
5941 -- identifier. The reason for killing it in the instance case is
5942 -- that it is common and reasonable for code to be deleted in
5943 -- instances for various reasons.
5945 -- Could we use Is_Statically_Unevaluated here???
5947 if Nkind
(Parent
(N
)) = N_If_Statement
then
5949 C
: constant Node_Id
:= Condition
(Parent
(N
));
5951 if Nkind
(C
) = N_Identifier
5954 or else (Present
(Entity
(C
))
5955 and then Has_Warnings_Off
(Entity
(C
))))
5962 -- Generate warning if not suppressed
5966 ("?t?this code can never be executed and has been deleted!",
5971 -- Recurse into block statements and bodies to process declarations
5974 if Nkind
(N
) = N_Block_Statement
5975 or else Nkind
(N
) = N_Subprogram_Body
5976 or else Nkind
(N
) = N_Package_Body
5978 Kill_Dead_Code
(Declarations
(N
), False);
5979 Kill_Dead_Code
(Statements
(Handled_Statement_Sequence
(N
)));
5981 if Nkind
(N
) = N_Subprogram_Body
then
5982 Set_Is_Eliminated
(Defining_Entity
(N
));
5985 elsif Nkind
(N
) = N_Package_Declaration
then
5986 Kill_Dead_Code
(Visible_Declarations
(Specification
(N
)));
5987 Kill_Dead_Code
(Private_Declarations
(Specification
(N
)));
5989 -- ??? After this point, Delete_Tree has been called on all
5990 -- declarations in Specification (N), so references to entities
5991 -- therein look suspicious.
5994 E
: Entity_Id
:= First_Entity
(Defining_Entity
(N
));
5997 while Present
(E
) loop
5998 if Ekind
(E
) = E_Operator
then
5999 Set_Is_Eliminated
(E
);
6006 -- Recurse into composite statement to kill individual statements in
6007 -- particular instantiations.
6009 elsif Nkind
(N
) = N_If_Statement
then
6010 Kill_Dead_Code
(Then_Statements
(N
));
6011 Kill_Dead_Code
(Elsif_Parts
(N
));
6012 Kill_Dead_Code
(Else_Statements
(N
));
6014 elsif Nkind
(N
) = N_Loop_Statement
then
6015 Kill_Dead_Code
(Statements
(N
));
6017 elsif Nkind
(N
) = N_Case_Statement
then
6021 Alt
:= First
(Alternatives
(N
));
6022 while Present
(Alt
) loop
6023 Kill_Dead_Code
(Statements
(Alt
));
6028 elsif Nkind
(N
) = N_Case_Statement_Alternative
then
6029 Kill_Dead_Code
(Statements
(N
));
6031 -- Deal with dead instances caused by deleting instantiations
6033 elsif Nkind
(N
) in N_Generic_Instantiation
then
6034 Remove_Dead_Instance
(N
);
6039 -- Case where argument is a list of nodes to be killed
6041 procedure Kill_Dead_Code
(L
: List_Id
; Warn
: Boolean := False) is
6048 if Is_Non_Empty_List
(L
) then
6050 while Present
(N
) loop
6051 Kill_Dead_Code
(N
, W
);
6058 ------------------------
6059 -- Known_Non_Negative --
6060 ------------------------
6062 function Known_Non_Negative
(Opnd
: Node_Id
) return Boolean is
6064 if Is_OK_Static_Expression
(Opnd
) and then Expr_Value
(Opnd
) >= 0 then
6069 Lo
: constant Node_Id
:= Type_Low_Bound
(Etype
(Opnd
));
6072 Is_OK_Static_Expression
(Lo
) and then Expr_Value
(Lo
) >= 0;
6075 end Known_Non_Negative
;
6077 --------------------
6078 -- Known_Non_Null --
6079 --------------------
6081 function Known_Non_Null
(N
: Node_Id
) return Boolean is
6083 -- Checks for case where N is an entity reference
6085 if Is_Entity_Name
(N
) and then Present
(Entity
(N
)) then
6087 E
: constant Entity_Id
:= Entity
(N
);
6092 -- First check if we are in decisive conditional
6094 Get_Current_Value_Condition
(N
, Op
, Val
);
6096 if Known_Null
(Val
) then
6097 if Op
= N_Op_Eq
then
6099 elsif Op
= N_Op_Ne
then
6104 -- If OK to do replacement, test Is_Known_Non_Null flag
6106 if OK_To_Do_Constant_Replacement
(E
) then
6107 return Is_Known_Non_Null
(E
);
6109 -- Otherwise if not safe to do replacement, then say so
6116 -- True if access attribute
6118 elsif Nkind
(N
) = N_Attribute_Reference
6119 and then Nam_In
(Attribute_Name
(N
), Name_Access
,
6120 Name_Unchecked_Access
,
6121 Name_Unrestricted_Access
)
6125 -- True if allocator
6127 elsif Nkind
(N
) = N_Allocator
then
6130 -- For a conversion, true if expression is known non-null
6132 elsif Nkind
(N
) = N_Type_Conversion
then
6133 return Known_Non_Null
(Expression
(N
));
6135 -- Above are all cases where the value could be determined to be
6136 -- non-null. In all other cases, we don't know, so return False.
6147 function Known_Null
(N
: Node_Id
) return Boolean is
6149 -- Checks for case where N is an entity reference
6151 if Is_Entity_Name
(N
) and then Present
(Entity
(N
)) then
6153 E
: constant Entity_Id
:= Entity
(N
);
6158 -- Constant null value is for sure null
6160 if Ekind
(E
) = E_Constant
6161 and then Known_Null
(Constant_Value
(E
))
6166 -- First check if we are in decisive conditional
6168 Get_Current_Value_Condition
(N
, Op
, Val
);
6170 if Known_Null
(Val
) then
6171 if Op
= N_Op_Eq
then
6173 elsif Op
= N_Op_Ne
then
6178 -- If OK to do replacement, test Is_Known_Null flag
6180 if OK_To_Do_Constant_Replacement
(E
) then
6181 return Is_Known_Null
(E
);
6183 -- Otherwise if not safe to do replacement, then say so
6190 -- True if explicit reference to null
6192 elsif Nkind
(N
) = N_Null
then
6195 -- For a conversion, true if expression is known null
6197 elsif Nkind
(N
) = N_Type_Conversion
then
6198 return Known_Null
(Expression
(N
));
6200 -- Above are all cases where the value could be determined to be null.
6201 -- In all other cases, we don't know, so return False.
6208 -----------------------------
6209 -- Make_CW_Equivalent_Type --
6210 -----------------------------
6212 -- Create a record type used as an equivalent of any member of the class
6213 -- which takes its size from exp.
6215 -- Generate the following code:
6217 -- type Equiv_T is record
6218 -- _parent : T (List of discriminant constraints taken from Exp);
6219 -- Ext__50 : Storage_Array (1 .. (Exp'size - Typ'object_size)/8);
6222 -- ??? Note that this type does not guarantee same alignment as all
6225 function Make_CW_Equivalent_Type
6227 E
: Node_Id
) return Entity_Id
6229 Loc
: constant Source_Ptr
:= Sloc
(E
);
6230 Root_Typ
: constant Entity_Id
:= Root_Type
(T
);
6231 List_Def
: constant List_Id
:= Empty_List
;
6232 Comp_List
: constant List_Id
:= New_List
;
6233 Equiv_Type
: Entity_Id
;
6234 Range_Type
: Entity_Id
;
6235 Str_Type
: Entity_Id
;
6236 Constr_Root
: Entity_Id
;
6240 -- If the root type is already constrained, there are no discriminants
6241 -- in the expression.
6243 if not Has_Discriminants
(Root_Typ
)
6244 or else Is_Constrained
(Root_Typ
)
6246 Constr_Root
:= Root_Typ
;
6248 -- At this point in the expansion, non-limited view of the type
6249 -- must be available, otherwise the error will be reported later.
6251 if From_Limited_With
(Constr_Root
)
6252 and then Present
(Non_Limited_View
(Constr_Root
))
6254 Constr_Root
:= Non_Limited_View
(Constr_Root
);
6258 Constr_Root
:= Make_Temporary
(Loc
, 'R');
6260 -- subtype cstr__n is T (List of discr constraints taken from Exp)
6262 Append_To
(List_Def
,
6263 Make_Subtype_Declaration
(Loc
,
6264 Defining_Identifier
=> Constr_Root
,
6265 Subtype_Indication
=> Make_Subtype_From_Expr
(E
, Root_Typ
)));
6268 -- Generate the range subtype declaration
6270 Range_Type
:= Make_Temporary
(Loc
, 'G');
6272 if not Is_Interface
(Root_Typ
) then
6274 -- subtype rg__xx is
6275 -- Storage_Offset range 1 .. (Expr'size - typ'size) / Storage_Unit
6278 Make_Op_Subtract
(Loc
,
6280 Make_Attribute_Reference
(Loc
,
6282 OK_Convert_To
(T
, Duplicate_Subexpr_No_Checks
(E
)),
6283 Attribute_Name
=> Name_Size
),
6285 Make_Attribute_Reference
(Loc
,
6286 Prefix
=> New_Occurrence_Of
(Constr_Root
, Loc
),
6287 Attribute_Name
=> Name_Object_Size
));
6289 -- subtype rg__xx is
6290 -- Storage_Offset range 1 .. Expr'size / Storage_Unit
6293 Make_Attribute_Reference
(Loc
,
6295 OK_Convert_To
(T
, Duplicate_Subexpr_No_Checks
(E
)),
6296 Attribute_Name
=> Name_Size
);
6299 Set_Paren_Count
(Sizexpr
, 1);
6301 Append_To
(List_Def
,
6302 Make_Subtype_Declaration
(Loc
,
6303 Defining_Identifier
=> Range_Type
,
6304 Subtype_Indication
=>
6305 Make_Subtype_Indication
(Loc
,
6306 Subtype_Mark
=> New_Occurrence_Of
(RTE
(RE_Storage_Offset
), Loc
),
6307 Constraint
=> Make_Range_Constraint
(Loc
,
6310 Low_Bound
=> Make_Integer_Literal
(Loc
, 1),
6312 Make_Op_Divide
(Loc
,
6313 Left_Opnd
=> Sizexpr
,
6314 Right_Opnd
=> Make_Integer_Literal
(Loc
,
6315 Intval
=> System_Storage_Unit
)))))));
6317 -- subtype str__nn is Storage_Array (rg__x);
6319 Str_Type
:= Make_Temporary
(Loc
, 'S');
6320 Append_To
(List_Def
,
6321 Make_Subtype_Declaration
(Loc
,
6322 Defining_Identifier
=> Str_Type
,
6323 Subtype_Indication
=>
6324 Make_Subtype_Indication
(Loc
,
6325 Subtype_Mark
=> New_Occurrence_Of
(RTE
(RE_Storage_Array
), Loc
),
6327 Make_Index_Or_Discriminant_Constraint
(Loc
,
6329 New_List
(New_Occurrence_Of
(Range_Type
, Loc
))))));
6331 -- type Equiv_T is record
6332 -- [ _parent : Tnn; ]
6336 Equiv_Type
:= Make_Temporary
(Loc
, 'T');
6337 Set_Ekind
(Equiv_Type
, E_Record_Type
);
6338 Set_Parent_Subtype
(Equiv_Type
, Constr_Root
);
6340 -- Set Is_Class_Wide_Equivalent_Type very early to trigger the special
6341 -- treatment for this type. In particular, even though _parent's type
6342 -- is a controlled type or contains controlled components, we do not
6343 -- want to set Has_Controlled_Component on it to avoid making it gain
6344 -- an unwanted _controller component.
6346 Set_Is_Class_Wide_Equivalent_Type
(Equiv_Type
);
6348 -- A class-wide equivalent type does not require initialization
6350 Set_Suppress_Initialization
(Equiv_Type
);
6352 if not Is_Interface
(Root_Typ
) then
6353 Append_To
(Comp_List
,
6354 Make_Component_Declaration
(Loc
,
6355 Defining_Identifier
=>
6356 Make_Defining_Identifier
(Loc
, Name_uParent
),
6357 Component_Definition
=>
6358 Make_Component_Definition
(Loc
,
6359 Aliased_Present
=> False,
6360 Subtype_Indication
=> New_Occurrence_Of
(Constr_Root
, Loc
))));
6363 Append_To
(Comp_List
,
6364 Make_Component_Declaration
(Loc
,
6365 Defining_Identifier
=> Make_Temporary
(Loc
, 'C'),
6366 Component_Definition
=>
6367 Make_Component_Definition
(Loc
,
6368 Aliased_Present
=> False,
6369 Subtype_Indication
=> New_Occurrence_Of
(Str_Type
, Loc
))));
6371 Append_To
(List_Def
,
6372 Make_Full_Type_Declaration
(Loc
,
6373 Defining_Identifier
=> Equiv_Type
,
6375 Make_Record_Definition
(Loc
,
6377 Make_Component_List
(Loc
,
6378 Component_Items
=> Comp_List
,
6379 Variant_Part
=> Empty
))));
6381 -- Suppress all checks during the analysis of the expanded code to avoid
6382 -- the generation of spurious warnings under ZFP run-time.
6384 Insert_Actions
(E
, List_Def
, Suppress
=> All_Checks
);
6386 end Make_CW_Equivalent_Type
;
6388 -------------------------
6389 -- Make_Invariant_Call --
6390 -------------------------
6392 function Make_Invariant_Call
(Expr
: Node_Id
) return Node_Id
is
6393 Loc
: constant Source_Ptr
:= Sloc
(Expr
);
6397 Typ
:= Etype
(Expr
);
6399 -- Subtypes may be subject to invariants coming from their respective
6400 -- base types. The subtype may be fully or partially private.
6402 if Ekind_In
(Typ
, E_Array_Subtype
,
6405 E_Record_Subtype_With_Private
)
6407 Typ
:= Base_Type
(Typ
);
6411 (Has_Invariants
(Typ
) and then Present
(Invariant_Procedure
(Typ
)));
6414 Make_Procedure_Call_Statement
(Loc
,
6416 New_Occurrence_Of
(Invariant_Procedure
(Typ
), Loc
),
6417 Parameter_Associations
=> New_List
(Relocate_Node
(Expr
)));
6418 end Make_Invariant_Call
;
6420 ------------------------
6421 -- Make_Literal_Range --
6422 ------------------------
6424 function Make_Literal_Range
6426 Literal_Typ
: Entity_Id
) return Node_Id
6428 Lo
: constant Node_Id
:=
6429 New_Copy_Tree
(String_Literal_Low_Bound
(Literal_Typ
));
6430 Index
: constant Entity_Id
:= Etype
(Lo
);
6433 Length_Expr
: constant Node_Id
:=
6434 Make_Op_Subtract
(Loc
,
6436 Make_Integer_Literal
(Loc
,
6437 Intval
=> String_Literal_Length
(Literal_Typ
)),
6439 Make_Integer_Literal
(Loc
, 1));
6442 Set_Analyzed
(Lo
, False);
6444 if Is_Integer_Type
(Index
) then
6447 Left_Opnd
=> New_Copy_Tree
(Lo
),
6448 Right_Opnd
=> Length_Expr
);
6451 Make_Attribute_Reference
(Loc
,
6452 Attribute_Name
=> Name_Val
,
6453 Prefix
=> New_Occurrence_Of
(Index
, Loc
),
6454 Expressions
=> New_List
(
6457 Make_Attribute_Reference
(Loc
,
6458 Attribute_Name
=> Name_Pos
,
6459 Prefix
=> New_Occurrence_Of
(Index
, Loc
),
6460 Expressions
=> New_List
(New_Copy_Tree
(Lo
))),
6461 Right_Opnd
=> Length_Expr
)));
6468 end Make_Literal_Range
;
6470 --------------------------
6471 -- Make_Non_Empty_Check --
6472 --------------------------
6474 function Make_Non_Empty_Check
6476 N
: Node_Id
) return Node_Id
6482 Make_Attribute_Reference
(Loc
,
6483 Attribute_Name
=> Name_Length
,
6484 Prefix
=> Duplicate_Subexpr_No_Checks
(N
, Name_Req
=> True)),
6486 Make_Integer_Literal
(Loc
, 0));
6487 end Make_Non_Empty_Check
;
6489 -------------------------
6490 -- Make_Predicate_Call --
6491 -------------------------
6493 function Make_Predicate_Call
6496 Mem
: Boolean := False) return Node_Id
6498 Loc
: constant Source_Ptr
:= Sloc
(Expr
);
6502 Save_Ghost_Mode
: constant Ghost_Mode_Type
:= Ghost_Mode
;
6505 pragma Assert
(Present
(Predicate_Function
(Typ
)));
6507 -- The related type may be subject to pragma Ghost. Set the mode now to
6508 -- ensure that the call is properly marked as Ghost.
6510 Set_Ghost_Mode_From_Entity
(Typ
);
6512 -- Call special membership version if requested and available
6515 PFM
:= Predicate_Function_M
(Typ
);
6517 if Present
(PFM
) then
6519 Make_Function_Call
(Loc
,
6520 Name
=> New_Occurrence_Of
(PFM
, Loc
),
6521 Parameter_Associations
=> New_List
(Relocate_Node
(Expr
)));
6523 Ghost_Mode
:= Save_Ghost_Mode
;
6528 -- Case of calling normal predicate function
6531 Make_Function_Call
(Loc
,
6533 New_Occurrence_Of
(Predicate_Function
(Typ
), Loc
),
6534 Parameter_Associations
=> New_List
(Relocate_Node
(Expr
)));
6536 Ghost_Mode
:= Save_Ghost_Mode
;
6538 end Make_Predicate_Call
;
6540 --------------------------
6541 -- Make_Predicate_Check --
6542 --------------------------
6544 function Make_Predicate_Check
6546 Expr
: Node_Id
) return Node_Id
6548 procedure Replace_Subtype_Reference
(N
: Node_Id
);
6549 -- Replace current occurrences of the subtype to which a dynamic
6550 -- predicate applies, by the expression that triggers a predicate
6551 -- check. This is needed for aspect Predicate_Failure, for which
6552 -- we do not generate a wrapper procedure, but simply modify the
6553 -- expression for the pragma of the predicate check.
6555 --------------------------------
6556 -- Replace_Subtype_Reference --
6557 --------------------------------
6559 procedure Replace_Subtype_Reference
(N
: Node_Id
) is
6561 Rewrite
(N
, New_Copy_Tree
(Expr
));
6563 -- We want to treat the node as if it comes from source, so
6564 -- that ASIS will not ignore it.
6566 Set_Comes_From_Source
(N
, True);
6567 end Replace_Subtype_Reference
;
6569 procedure Replace_Subtype_References
is
6570 new Replace_Type_References_Generic
(Replace_Subtype_Reference
);
6574 Loc
: constant Source_Ptr
:= Sloc
(Expr
);
6576 Fail_Expr
: Node_Id
;
6579 -- Start of processing for Make_Predicate_Check
6582 -- If predicate checks are suppressed, then return a null statement. For
6583 -- this call, we check only the scope setting. If the caller wants to
6584 -- check a specific entity's setting, they must do it manually.
6586 if Predicate_Checks_Suppressed
(Empty
) then
6587 return Make_Null_Statement
(Loc
);
6590 -- Do not generate a check within an internal subprogram (stream
6591 -- functions and the like, including including predicate functions).
6593 if Within_Internal_Subprogram
then
6594 return Make_Null_Statement
(Loc
);
6597 -- Compute proper name to use, we need to get this right so that the
6598 -- right set of check policies apply to the Check pragma we are making.
6600 if Has_Dynamic_Predicate_Aspect
(Typ
) then
6601 Nam
:= Name_Dynamic_Predicate
;
6602 elsif Has_Static_Predicate_Aspect
(Typ
) then
6603 Nam
:= Name_Static_Predicate
;
6605 Nam
:= Name_Predicate
;
6608 Arg_List
:= New_List
(
6609 Make_Pragma_Argument_Association
(Loc
,
6610 Expression
=> Make_Identifier
(Loc
, Nam
)),
6611 Make_Pragma_Argument_Association
(Loc
,
6612 Expression
=> Make_Predicate_Call
(Typ
, Expr
)));
6614 -- If subtype has Predicate_Failure defined, add the correponding
6615 -- expression as an additional pragma parameter, after replacing
6616 -- current instances with the expression being checked.
6618 if Has_Aspect
(Typ
, Aspect_Predicate_Failure
) then
6621 (Expression
(Find_Aspect
(Typ
, Aspect_Predicate_Failure
)));
6622 Replace_Subtype_References
(Fail_Expr
, Typ
);
6624 Append_To
(Arg_List
,
6625 Make_Pragma_Argument_Association
(Loc
,
6626 Expression
=> Fail_Expr
));
6631 Pragma_Identifier
=> Make_Identifier
(Loc
, Name_Check
),
6632 Pragma_Argument_Associations
=> Arg_List
);
6633 end Make_Predicate_Check
;
6635 ----------------------------
6636 -- Make_Subtype_From_Expr --
6637 ----------------------------
6639 -- 1. If Expr is an unconstrained array expression, creates
6640 -- Unc_Type(Expr'first(1)..Expr'last(1),..., Expr'first(n)..Expr'last(n))
6642 -- 2. If Expr is a unconstrained discriminated type expression, creates
6643 -- Unc_Type(Expr.Discr1, ... , Expr.Discr_n)
6645 -- 3. If Expr is class-wide, creates an implicit class-wide subtype
6647 function Make_Subtype_From_Expr
6649 Unc_Typ
: Entity_Id
;
6650 Related_Id
: Entity_Id
:= Empty
) return Node_Id
6652 List_Constr
: constant List_Id
:= New_List
;
6653 Loc
: constant Source_Ptr
:= Sloc
(E
);
6656 Full_Subtyp
: Entity_Id
;
6657 High_Bound
: Entity_Id
;
6658 Index_Typ
: Entity_Id
;
6659 Low_Bound
: Entity_Id
;
6660 Priv_Subtyp
: Entity_Id
;
6664 if Is_Private_Type
(Unc_Typ
)
6665 and then Has_Unknown_Discriminants
(Unc_Typ
)
6667 -- The caller requests a unique external name for both the private
6668 -- and the full subtype.
6670 if Present
(Related_Id
) then
6672 Make_Defining_Identifier
(Loc
,
6673 Chars
=> New_External_Name
(Chars
(Related_Id
), 'C'));
6675 Make_Defining_Identifier
(Loc
,
6676 Chars
=> New_External_Name
(Chars
(Related_Id
), 'P'));
6679 Full_Subtyp
:= Make_Temporary
(Loc
, 'C');
6680 Priv_Subtyp
:= Make_Temporary
(Loc
, 'P');
6683 -- Prepare the subtype completion. Use the base type to find the
6684 -- underlying type because the type may be a generic actual or an
6685 -- explicit subtype.
6687 Utyp
:= Underlying_Type
(Base_Type
(Unc_Typ
));
6690 Unchecked_Convert_To
(Utyp
, Duplicate_Subexpr_No_Checks
(E
));
6691 Set_Parent
(Full_Exp
, Parent
(E
));
6694 Make_Subtype_Declaration
(Loc
,
6695 Defining_Identifier
=> Full_Subtyp
,
6696 Subtype_Indication
=> Make_Subtype_From_Expr
(Full_Exp
, Utyp
)));
6698 -- Define the dummy private subtype
6700 Set_Ekind
(Priv_Subtyp
, Subtype_Kind
(Ekind
(Unc_Typ
)));
6701 Set_Etype
(Priv_Subtyp
, Base_Type
(Unc_Typ
));
6702 Set_Scope
(Priv_Subtyp
, Full_Subtyp
);
6703 Set_Is_Constrained
(Priv_Subtyp
);
6704 Set_Is_Tagged_Type
(Priv_Subtyp
, Is_Tagged_Type
(Unc_Typ
));
6705 Set_Is_Itype
(Priv_Subtyp
);
6706 Set_Associated_Node_For_Itype
(Priv_Subtyp
, E
);
6708 if Is_Tagged_Type
(Priv_Subtyp
) then
6710 (Base_Type
(Priv_Subtyp
), Class_Wide_Type
(Unc_Typ
));
6711 Set_Direct_Primitive_Operations
(Priv_Subtyp
,
6712 Direct_Primitive_Operations
(Unc_Typ
));
6715 Set_Full_View
(Priv_Subtyp
, Full_Subtyp
);
6717 return New_Occurrence_Of
(Priv_Subtyp
, Loc
);
6719 elsif Is_Array_Type
(Unc_Typ
) then
6720 Index_Typ
:= First_Index
(Unc_Typ
);
6721 for J
in 1 .. Number_Dimensions
(Unc_Typ
) loop
6723 -- Capture the bounds of each index constraint in case the context
6724 -- is an object declaration of an unconstrained type initialized
6725 -- by a function call:
6727 -- Obj : Unconstr_Typ := Func_Call;
6729 -- This scenario requires secondary scope management and the index
6730 -- constraint cannot depend on the temporary used to capture the
6731 -- result of the function call.
6734 -- Temp : Unconstr_Typ_Ptr := Func_Call'reference;
6735 -- subtype S is Unconstr_Typ (Temp.all'First .. Temp.all'Last);
6736 -- Obj : S := Temp.all;
6737 -- SS_Release; -- Temp is gone at this point, bounds of S are
6741 -- Low_Bound : constant Base_Type (Index_Typ) := E'First (J);
6743 Low_Bound
:= Make_Temporary
(Loc
, 'B');
6745 Make_Object_Declaration
(Loc
,
6746 Defining_Identifier
=> Low_Bound
,
6747 Object_Definition
=>
6748 New_Occurrence_Of
(Base_Type
(Etype
(Index_Typ
)), Loc
),
6749 Constant_Present
=> True,
6751 Make_Attribute_Reference
(Loc
,
6752 Prefix
=> Duplicate_Subexpr_No_Checks
(E
),
6753 Attribute_Name
=> Name_First
,
6754 Expressions
=> New_List
(
6755 Make_Integer_Literal
(Loc
, J
)))));
6758 -- High_Bound : constant Base_Type (Index_Typ) := E'Last (J);
6760 High_Bound
:= Make_Temporary
(Loc
, 'B');
6762 Make_Object_Declaration
(Loc
,
6763 Defining_Identifier
=> High_Bound
,
6764 Object_Definition
=>
6765 New_Occurrence_Of
(Base_Type
(Etype
(Index_Typ
)), Loc
),
6766 Constant_Present
=> True,
6768 Make_Attribute_Reference
(Loc
,
6769 Prefix
=> Duplicate_Subexpr_No_Checks
(E
),
6770 Attribute_Name
=> Name_Last
,
6771 Expressions
=> New_List
(
6772 Make_Integer_Literal
(Loc
, J
)))));
6774 Append_To
(List_Constr
,
6776 Low_Bound
=> New_Occurrence_Of
(Low_Bound
, Loc
),
6777 High_Bound
=> New_Occurrence_Of
(High_Bound
, Loc
)));
6779 Index_Typ
:= Next_Index
(Index_Typ
);
6782 elsif Is_Class_Wide_Type
(Unc_Typ
) then
6784 CW_Subtype
: Entity_Id
;
6785 EQ_Typ
: Entity_Id
:= Empty
;
6788 -- A class-wide equivalent type is not needed on VM targets
6789 -- because the VM back-ends handle the class-wide object
6790 -- initialization itself (and doesn't need or want the
6791 -- additional intermediate type to handle the assignment).
6793 if Expander_Active
and then Tagged_Type_Expansion
then
6795 -- If this is the class-wide type of a completion that is a
6796 -- record subtype, set the type of the class-wide type to be
6797 -- the full base type, for use in the expanded code for the
6798 -- equivalent type. Should this be done earlier when the
6799 -- completion is analyzed ???
6801 if Is_Private_Type
(Etype
(Unc_Typ
))
6803 Ekind
(Full_View
(Etype
(Unc_Typ
))) = E_Record_Subtype
6805 Set_Etype
(Unc_Typ
, Base_Type
(Full_View
(Etype
(Unc_Typ
))));
6808 EQ_Typ
:= Make_CW_Equivalent_Type
(Unc_Typ
, E
);
6811 CW_Subtype
:= New_Class_Wide_Subtype
(Unc_Typ
, E
);
6812 Set_Equivalent_Type
(CW_Subtype
, EQ_Typ
);
6813 Set_Cloned_Subtype
(CW_Subtype
, Base_Type
(Unc_Typ
));
6815 return New_Occurrence_Of
(CW_Subtype
, Loc
);
6818 -- Indefinite record type with discriminants
6821 D
:= First_Discriminant
(Unc_Typ
);
6822 while Present
(D
) loop
6823 Append_To
(List_Constr
,
6824 Make_Selected_Component
(Loc
,
6825 Prefix
=> Duplicate_Subexpr_No_Checks
(E
),
6826 Selector_Name
=> New_Occurrence_Of
(D
, Loc
)));
6828 Next_Discriminant
(D
);
6833 Make_Subtype_Indication
(Loc
,
6834 Subtype_Mark
=> New_Occurrence_Of
(Unc_Typ
, Loc
),
6836 Make_Index_Or_Discriminant_Constraint
(Loc
,
6837 Constraints
=> List_Constr
));
6838 end Make_Subtype_From_Expr
;
6840 ----------------------------
6841 -- Matching_Standard_Type --
6842 ----------------------------
6844 function Matching_Standard_Type
(Typ
: Entity_Id
) return Entity_Id
is
6845 pragma Assert
(Is_Scalar_Type
(Typ
));
6846 Siz
: constant Uint
:= Esize
(Typ
);
6849 -- Floating-point cases
6851 if Is_Floating_Point_Type
(Typ
) then
6852 if Siz
<= Esize
(Standard_Short_Float
) then
6853 return Standard_Short_Float
;
6854 elsif Siz
<= Esize
(Standard_Float
) then
6855 return Standard_Float
;
6856 elsif Siz
<= Esize
(Standard_Long_Float
) then
6857 return Standard_Long_Float
;
6858 elsif Siz
<= Esize
(Standard_Long_Long_Float
) then
6859 return Standard_Long_Long_Float
;
6861 raise Program_Error
;
6864 -- Integer cases (includes fixed-point types)
6866 -- Unsigned integer cases (includes normal enumeration types)
6868 elsif Is_Unsigned_Type
(Typ
) then
6869 if Siz
<= Esize
(Standard_Short_Short_Unsigned
) then
6870 return Standard_Short_Short_Unsigned
;
6871 elsif Siz
<= Esize
(Standard_Short_Unsigned
) then
6872 return Standard_Short_Unsigned
;
6873 elsif Siz
<= Esize
(Standard_Unsigned
) then
6874 return Standard_Unsigned
;
6875 elsif Siz
<= Esize
(Standard_Long_Unsigned
) then
6876 return Standard_Long_Unsigned
;
6877 elsif Siz
<= Esize
(Standard_Long_Long_Unsigned
) then
6878 return Standard_Long_Long_Unsigned
;
6880 raise Program_Error
;
6883 -- Signed integer cases
6886 if Siz
<= Esize
(Standard_Short_Short_Integer
) then
6887 return Standard_Short_Short_Integer
;
6888 elsif Siz
<= Esize
(Standard_Short_Integer
) then
6889 return Standard_Short_Integer
;
6890 elsif Siz
<= Esize
(Standard_Integer
) then
6891 return Standard_Integer
;
6892 elsif Siz
<= Esize
(Standard_Long_Integer
) then
6893 return Standard_Long_Integer
;
6894 elsif Siz
<= Esize
(Standard_Long_Long_Integer
) then
6895 return Standard_Long_Long_Integer
;
6897 raise Program_Error
;
6900 end Matching_Standard_Type
;
6902 -----------------------------
6903 -- May_Generate_Large_Temp --
6904 -----------------------------
6906 -- At the current time, the only types that we return False for (i.e. where
6907 -- we decide we know they cannot generate large temps) are ones where we
6908 -- know the size is 256 bits or less at compile time, and we are still not
6909 -- doing a thorough job on arrays and records ???
6911 function May_Generate_Large_Temp
(Typ
: Entity_Id
) return Boolean is
6913 if not Size_Known_At_Compile_Time
(Typ
) then
6916 elsif Esize
(Typ
) /= 0 and then Esize
(Typ
) <= 256 then
6919 elsif Is_Array_Type
(Typ
)
6920 and then Present
(Packed_Array_Impl_Type
(Typ
))
6922 return May_Generate_Large_Temp
(Packed_Array_Impl_Type
(Typ
));
6924 -- We could do more here to find other small types ???
6929 end May_Generate_Large_Temp
;
6931 ------------------------
6932 -- Needs_Finalization --
6933 ------------------------
6935 function Needs_Finalization
(T
: Entity_Id
) return Boolean is
6936 function Has_Some_Controlled_Component
(Rec
: Entity_Id
) return Boolean;
6937 -- If type is not frozen yet, check explicitly among its components,
6938 -- because the Has_Controlled_Component flag is not necessarily set.
6940 -----------------------------------
6941 -- Has_Some_Controlled_Component --
6942 -----------------------------------
6944 function Has_Some_Controlled_Component
6945 (Rec
: Entity_Id
) return Boolean
6950 if Has_Controlled_Component
(Rec
) then
6953 elsif not Is_Frozen
(Rec
) then
6954 if Is_Record_Type
(Rec
) then
6955 Comp
:= First_Entity
(Rec
);
6957 while Present
(Comp
) loop
6958 if not Is_Type
(Comp
)
6959 and then Needs_Finalization
(Etype
(Comp
))
6972 and then Needs_Finalization
(Component_Type
(Rec
));
6977 end Has_Some_Controlled_Component
;
6979 -- Start of processing for Needs_Finalization
6982 -- Certain run-time configurations and targets do not provide support
6983 -- for controlled types.
6985 if Restriction_Active
(No_Finalization
) then
6988 -- C++ types are not considered controlled. It is assumed that the
6989 -- non-Ada side will handle their clean up.
6991 elsif Convention
(T
) = Convention_CPP
then
6994 -- Never needs finalization if Disable_Controlled set
6996 elsif Disable_Controlled
(T
) then
6999 elsif Is_Class_Wide_Type
(T
) and then Disable_Controlled
(Etype
(T
)) then
7003 -- Class-wide types are treated as controlled because derivations
7004 -- from the root type can introduce controlled components.
7006 return Is_Class_Wide_Type
(T
)
7007 or else Is_Controlled
(T
)
7008 or else Has_Some_Controlled_Component
(T
)
7010 (Is_Concurrent_Type
(T
)
7011 and then Present
(Corresponding_Record_Type
(T
))
7012 and then Needs_Finalization
(Corresponding_Record_Type
(T
)));
7014 end Needs_Finalization
;
7016 ----------------------------
7017 -- Needs_Constant_Address --
7018 ----------------------------
7020 function Needs_Constant_Address
7022 Typ
: Entity_Id
) return Boolean
7026 -- If we have no initialization of any kind, then we don't need to place
7027 -- any restrictions on the address clause, because the object will be
7028 -- elaborated after the address clause is evaluated. This happens if the
7029 -- declaration has no initial expression, or the type has no implicit
7030 -- initialization, or the object is imported.
7032 -- The same holds for all initialized scalar types and all access types.
7033 -- Packed bit arrays of size up to 64 are represented using a modular
7034 -- type with an initialization (to zero) and can be processed like other
7035 -- initialized scalar types.
7037 -- If the type is controlled, code to attach the object to a
7038 -- finalization chain is generated at the point of declaration, and
7039 -- therefore the elaboration of the object cannot be delayed: the
7040 -- address expression must be a constant.
7042 if No
(Expression
(Decl
))
7043 and then not Needs_Finalization
(Typ
)
7045 (not Has_Non_Null_Base_Init_Proc
(Typ
)
7046 or else Is_Imported
(Defining_Identifier
(Decl
)))
7050 elsif (Present
(Expression
(Decl
)) and then Is_Scalar_Type
(Typ
))
7051 or else Is_Access_Type
(Typ
)
7053 (Is_Bit_Packed_Array
(Typ
)
7054 and then Is_Modular_Integer_Type
(Packed_Array_Impl_Type
(Typ
)))
7060 -- Otherwise, we require the address clause to be constant because
7061 -- the call to the initialization procedure (or the attach code) has
7062 -- to happen at the point of the declaration.
7064 -- Actually the IP call has been moved to the freeze actions anyway,
7065 -- so maybe we can relax this restriction???
7069 end Needs_Constant_Address
;
7071 ----------------------------
7072 -- New_Class_Wide_Subtype --
7073 ----------------------------
7075 function New_Class_Wide_Subtype
7076 (CW_Typ
: Entity_Id
;
7077 N
: Node_Id
) return Entity_Id
7079 Res
: constant Entity_Id
:= Create_Itype
(E_Void
, N
);
7080 Res_Name
: constant Name_Id
:= Chars
(Res
);
7081 Res_Scope
: constant Entity_Id
:= Scope
(Res
);
7084 Copy_Node
(CW_Typ
, Res
);
7085 Set_Comes_From_Source
(Res
, False);
7086 Set_Sloc
(Res
, Sloc
(N
));
7088 Set_Associated_Node_For_Itype
(Res
, N
);
7089 Set_Is_Public
(Res
, False); -- By default, may be changed below.
7090 Set_Public_Status
(Res
);
7091 Set_Chars
(Res
, Res_Name
);
7092 Set_Scope
(Res
, Res_Scope
);
7093 Set_Ekind
(Res
, E_Class_Wide_Subtype
);
7094 Set_Next_Entity
(Res
, Empty
);
7095 Set_Etype
(Res
, Base_Type
(CW_Typ
));
7096 Set_Is_Frozen
(Res
, False);
7097 Set_Freeze_Node
(Res
, Empty
);
7099 end New_Class_Wide_Subtype
;
7101 --------------------------------
7102 -- Non_Limited_Designated_Type --
7103 ---------------------------------
7105 function Non_Limited_Designated_Type
(T
: Entity_Id
) return Entity_Id
is
7106 Desig
: constant Entity_Id
:= Designated_Type
(T
);
7108 if Has_Non_Limited_View
(Desig
) then
7109 return Non_Limited_View
(Desig
);
7113 end Non_Limited_Designated_Type
;
7115 -----------------------------------
7116 -- OK_To_Do_Constant_Replacement --
7117 -----------------------------------
7119 function OK_To_Do_Constant_Replacement
(E
: Entity_Id
) return Boolean is
7120 ES
: constant Entity_Id
:= Scope
(E
);
7124 -- Do not replace statically allocated objects, because they may be
7125 -- modified outside the current scope.
7127 if Is_Statically_Allocated
(E
) then
7130 -- Do not replace aliased or volatile objects, since we don't know what
7131 -- else might change the value.
7133 elsif Is_Aliased
(E
) or else Treat_As_Volatile
(E
) then
7136 -- Debug flag -gnatdM disconnects this optimization
7138 elsif Debug_Flag_MM
then
7141 -- Otherwise check scopes
7144 CS
:= Current_Scope
;
7147 -- If we are in right scope, replacement is safe
7152 -- Packages do not affect the determination of safety
7154 elsif Ekind
(CS
) = E_Package
then
7155 exit when CS
= Standard_Standard
;
7158 -- Blocks do not affect the determination of safety
7160 elsif Ekind
(CS
) = E_Block
then
7163 -- Loops do not affect the determination of safety. Note that we
7164 -- kill all current values on entry to a loop, so we are just
7165 -- talking about processing within a loop here.
7167 elsif Ekind
(CS
) = E_Loop
then
7170 -- Otherwise, the reference is dubious, and we cannot be sure that
7171 -- it is safe to do the replacement.
7180 end OK_To_Do_Constant_Replacement
;
7182 ------------------------------------
7183 -- Possible_Bit_Aligned_Component --
7184 ------------------------------------
7186 function Possible_Bit_Aligned_Component
(N
: Node_Id
) return Boolean is
7188 -- Do not process an unanalyzed node because it is not yet decorated and
7189 -- most checks performed below will fail.
7191 if not Analyzed
(N
) then
7197 -- Case of indexed component
7199 when N_Indexed_Component
=>
7201 P
: constant Node_Id
:= Prefix
(N
);
7202 Ptyp
: constant Entity_Id
:= Etype
(P
);
7205 -- If we know the component size and it is less than 64, then
7206 -- we are definitely OK. The back end always does assignment of
7207 -- misaligned small objects correctly.
7209 if Known_Static_Component_Size
(Ptyp
)
7210 and then Component_Size
(Ptyp
) <= 64
7214 -- Otherwise, we need to test the prefix, to see if we are
7215 -- indexing from a possibly unaligned component.
7218 return Possible_Bit_Aligned_Component
(P
);
7222 -- Case of selected component
7224 when N_Selected_Component
=>
7226 P
: constant Node_Id
:= Prefix
(N
);
7227 Comp
: constant Entity_Id
:= Entity
(Selector_Name
(N
));
7230 -- If there is no component clause, then we are in the clear
7231 -- since the back end will never misalign a large component
7232 -- unless it is forced to do so. In the clear means we need
7233 -- only the recursive test on the prefix.
7235 if Component_May_Be_Bit_Aligned
(Comp
) then
7238 return Possible_Bit_Aligned_Component
(P
);
7242 -- For a slice, test the prefix, if that is possibly misaligned,
7243 -- then for sure the slice is.
7246 return Possible_Bit_Aligned_Component
(Prefix
(N
));
7248 -- For an unchecked conversion, check whether the expression may
7251 when N_Unchecked_Type_Conversion
=>
7252 return Possible_Bit_Aligned_Component
(Expression
(N
));
7254 -- If we have none of the above, it means that we have fallen off the
7255 -- top testing prefixes recursively, and we now have a stand alone
7256 -- object, where we don't have a problem, unless this is a renaming,
7257 -- in which case we need to look into the renamed object.
7260 if Is_Entity_Name
(N
)
7261 and then Present
(Renamed_Object
(Entity
(N
)))
7264 Possible_Bit_Aligned_Component
(Renamed_Object
(Entity
(N
)));
7270 end Possible_Bit_Aligned_Component
;
7272 -----------------------------------------------
7273 -- Process_Statements_For_Controlled_Objects --
7274 -----------------------------------------------
7276 procedure Process_Statements_For_Controlled_Objects
(N
: Node_Id
) is
7277 Loc
: constant Source_Ptr
:= Sloc
(N
);
7279 function Are_Wrapped
(L
: List_Id
) return Boolean;
7280 -- Determine whether list L contains only one statement which is a block
7282 function Wrap_Statements_In_Block
7284 Scop
: Entity_Id
:= Current_Scope
) return Node_Id
;
7285 -- Given a list of statements L, wrap it in a block statement and return
7286 -- the generated node. Scop is either the current scope or the scope of
7287 -- the context (if applicable).
7293 function Are_Wrapped
(L
: List_Id
) return Boolean is
7294 Stmt
: constant Node_Id
:= First
(L
);
7298 and then No
(Next
(Stmt
))
7299 and then Nkind
(Stmt
) = N_Block_Statement
;
7302 ------------------------------
7303 -- Wrap_Statements_In_Block --
7304 ------------------------------
7306 function Wrap_Statements_In_Block
7308 Scop
: Entity_Id
:= Current_Scope
) return Node_Id
7310 Block_Id
: Entity_Id
;
7311 Block_Nod
: Node_Id
;
7312 Iter_Loop
: Entity_Id
;
7316 Make_Block_Statement
(Loc
,
7317 Declarations
=> No_List
,
7318 Handled_Statement_Sequence
=>
7319 Make_Handled_Sequence_Of_Statements
(Loc
,
7322 -- Create a label for the block in case the block needs to manage the
7323 -- secondary stack. A label allows for flag Uses_Sec_Stack to be set.
7325 Add_Block_Identifier
(Block_Nod
, Block_Id
);
7327 -- When wrapping the statements of an iterator loop, check whether
7328 -- the loop requires secondary stack management and if so, propagate
7329 -- the appropriate flags to the block. This ensures that the cursor
7330 -- is properly cleaned up at each iteration of the loop.
7332 Iter_Loop
:= Find_Enclosing_Iterator_Loop
(Scop
);
7334 if Present
(Iter_Loop
) then
7335 Set_Uses_Sec_Stack
(Block_Id
, Uses_Sec_Stack
(Iter_Loop
));
7337 -- Secondary stack reclamation is suppressed when the associated
7338 -- iterator loop contains a return statement which uses the stack.
7340 Set_Sec_Stack_Needed_For_Return
7341 (Block_Id
, Sec_Stack_Needed_For_Return
(Iter_Loop
));
7345 end Wrap_Statements_In_Block
;
7351 -- Start of processing for Process_Statements_For_Controlled_Objects
7354 -- Whenever a non-handled statement list is wrapped in a block, the
7355 -- block must be explicitly analyzed to redecorate all entities in the
7356 -- list and ensure that a finalizer is properly built.
7361 N_Conditional_Entry_Call |
7362 N_Selective_Accept
=>
7364 -- Check the "then statements" for elsif parts and if statements
7366 if Nkind_In
(N
, N_Elsif_Part
, N_If_Statement
)
7367 and then not Is_Empty_List
(Then_Statements
(N
))
7368 and then not Are_Wrapped
(Then_Statements
(N
))
7369 and then Requires_Cleanup_Actions
7370 (Then_Statements
(N
), False, False)
7372 Block
:= Wrap_Statements_In_Block
(Then_Statements
(N
));
7373 Set_Then_Statements
(N
, New_List
(Block
));
7378 -- Check the "else statements" for conditional entry calls, if
7379 -- statements and selective accepts.
7381 if Nkind_In
(N
, N_Conditional_Entry_Call
,
7384 and then not Is_Empty_List
(Else_Statements
(N
))
7385 and then not Are_Wrapped
(Else_Statements
(N
))
7386 and then Requires_Cleanup_Actions
7387 (Else_Statements
(N
), False, False)
7389 Block
:= Wrap_Statements_In_Block
(Else_Statements
(N
));
7390 Set_Else_Statements
(N
, New_List
(Block
));
7395 when N_Abortable_Part |
7396 N_Accept_Alternative |
7397 N_Case_Statement_Alternative |
7398 N_Delay_Alternative |
7399 N_Entry_Call_Alternative |
7400 N_Exception_Handler |
7402 N_Triggering_Alternative
=>
7404 if not Is_Empty_List
(Statements
(N
))
7405 and then not Are_Wrapped
(Statements
(N
))
7406 and then Requires_Cleanup_Actions
(Statements
(N
), False, False)
7408 if Nkind
(N
) = N_Loop_Statement
7409 and then Present
(Identifier
(N
))
7412 Wrap_Statements_In_Block
7413 (L
=> Statements
(N
),
7414 Scop
=> Entity
(Identifier
(N
)));
7416 Block
:= Wrap_Statements_In_Block
(Statements
(N
));
7419 Set_Statements
(N
, New_List
(Block
));
7426 end Process_Statements_For_Controlled_Objects
;
7432 function Power_Of_Two
(N
: Node_Id
) return Nat
is
7433 Typ
: constant Entity_Id
:= Etype
(N
);
7434 pragma Assert
(Is_Integer_Type
(Typ
));
7436 Siz
: constant Nat
:= UI_To_Int
(Esize
(Typ
));
7440 if not Compile_Time_Known_Value
(N
) then
7444 Val
:= Expr_Value
(N
);
7445 for J
in 1 .. Siz
- 1 loop
7446 if Val
= Uint_2
** J
then
7455 ----------------------
7456 -- Remove_Init_Call --
7457 ----------------------
7459 function Remove_Init_Call
7461 Rep_Clause
: Node_Id
) return Node_Id
7463 Par
: constant Node_Id
:= Parent
(Var
);
7464 Typ
: constant Entity_Id
:= Etype
(Var
);
7466 Init_Proc
: Entity_Id
;
7467 -- Initialization procedure for Typ
7469 function Find_Init_Call_In_List
(From
: Node_Id
) return Node_Id
;
7470 -- Look for init call for Var starting at From and scanning the
7471 -- enclosing list until Rep_Clause or the end of the list is reached.
7473 ----------------------------
7474 -- Find_Init_Call_In_List --
7475 ----------------------------
7477 function Find_Init_Call_In_List
(From
: Node_Id
) return Node_Id
is
7478 Init_Call
: Node_Id
;
7482 while Present
(Init_Call
) and then Init_Call
/= Rep_Clause
loop
7483 if Nkind
(Init_Call
) = N_Procedure_Call_Statement
7484 and then Is_Entity_Name
(Name
(Init_Call
))
7485 and then Entity
(Name
(Init_Call
)) = Init_Proc
7494 end Find_Init_Call_In_List
;
7496 Init_Call
: Node_Id
;
7498 -- Start of processing for Find_Init_Call
7501 if Present
(Initialization_Statements
(Var
)) then
7502 Init_Call
:= Initialization_Statements
(Var
);
7503 Set_Initialization_Statements
(Var
, Empty
);
7505 elsif not Has_Non_Null_Base_Init_Proc
(Typ
) then
7507 -- No init proc for the type, so obviously no call to be found
7512 -- We might be able to handle other cases below by just properly
7513 -- setting Initialization_Statements at the point where the init proc
7514 -- call is generated???
7516 Init_Proc
:= Base_Init_Proc
(Typ
);
7518 -- First scan the list containing the declaration of Var
7520 Init_Call
:= Find_Init_Call_In_List
(From
=> Next
(Par
));
7522 -- If not found, also look on Var's freeze actions list, if any,
7523 -- since the init call may have been moved there (case of an address
7524 -- clause applying to Var).
7526 if No
(Init_Call
) and then Present
(Freeze_Node
(Var
)) then
7528 Find_Init_Call_In_List
(First
(Actions
(Freeze_Node
(Var
))));
7531 -- If the initialization call has actuals that use the secondary
7532 -- stack, the call may have been wrapped into a temporary block, in
7533 -- which case the block itself has to be removed.
7535 if No
(Init_Call
) and then Nkind
(Next
(Par
)) = N_Block_Statement
then
7537 Blk
: constant Node_Id
:= Next
(Par
);
7540 (Find_Init_Call_In_List
7541 (First
(Statements
(Handled_Statement_Sequence
(Blk
)))))
7549 if Present
(Init_Call
) then
7553 end Remove_Init_Call
;
7555 -------------------------
7556 -- Remove_Side_Effects --
7557 -------------------------
7559 procedure Remove_Side_Effects
7561 Name_Req
: Boolean := False;
7562 Renaming_Req
: Boolean := False;
7563 Variable_Ref
: Boolean := False;
7564 Related_Id
: Entity_Id
:= Empty
;
7565 Is_Low_Bound
: Boolean := False;
7566 Is_High_Bound
: Boolean := False;
7567 Check_Side_Effects
: Boolean := True)
7569 function Build_Temporary
7572 Related_Nod
: Node_Id
:= Empty
) return Entity_Id
;
7573 -- Create an external symbol of the form xxx_FIRST/_LAST if Related_Nod
7574 -- is present (xxx is taken from the Chars field of Related_Nod),
7575 -- otherwise it generates an internal temporary.
7577 function Is_Name_Reference
(N
: Node_Id
) return Boolean;
7578 -- Determine if the tree referenced by N represents a name. This is
7579 -- similar to Is_Object_Reference but returns true only if N can be
7580 -- renamed without the need for a temporary, the typical example of
7581 -- an object not in this category being a function call.
7583 ---------------------
7584 -- Build_Temporary --
7585 ---------------------
7587 function Build_Temporary
7590 Related_Nod
: Node_Id
:= Empty
) return Entity_Id
7595 -- The context requires an external symbol
7597 if Present
(Related_Id
) then
7598 if Is_Low_Bound
then
7599 Temp_Nam
:= New_External_Name
(Chars
(Related_Id
), "_FIRST");
7600 else pragma Assert
(Is_High_Bound
);
7601 Temp_Nam
:= New_External_Name
(Chars
(Related_Id
), "_LAST");
7604 return Make_Defining_Identifier
(Loc
, Temp_Nam
);
7606 -- Otherwise generate an internal temporary
7609 return Make_Temporary
(Loc
, Id
, Related_Nod
);
7611 end Build_Temporary
;
7613 -----------------------
7614 -- Is_Name_Reference --
7615 -----------------------
7617 function Is_Name_Reference
(N
: Node_Id
) return Boolean is
7619 if Is_Entity_Name
(N
) then
7620 return Present
(Entity
(N
)) and then Is_Object
(Entity
(N
));
7624 when N_Indexed_Component | N_Slice
=>
7626 Is_Name_Reference
(Prefix
(N
))
7627 or else Is_Access_Type
(Etype
(Prefix
(N
)));
7629 -- Attributes 'Input, 'Old and 'Result produce objects
7631 when N_Attribute_Reference
=>
7634 (Attribute_Name
(N
), Name_Input
, Name_Old
, Name_Result
);
7636 when N_Selected_Component
=>
7638 Is_Name_Reference
(Selector_Name
(N
))
7640 (Is_Name_Reference
(Prefix
(N
))
7641 or else Is_Access_Type
(Etype
(Prefix
(N
))));
7643 when N_Explicit_Dereference
=>
7646 -- A view conversion of a tagged name is a name reference
7648 when N_Type_Conversion
=>
7649 return Is_Tagged_Type
(Etype
(Subtype_Mark
(N
)))
7650 and then Is_Tagged_Type
(Etype
(Expression
(N
)))
7651 and then Is_Name_Reference
(Expression
(N
));
7653 -- An unchecked type conversion is considered to be a name if
7654 -- the operand is a name (this construction arises only as a
7655 -- result of expansion activities).
7657 when N_Unchecked_Type_Conversion
=>
7658 return Is_Name_Reference
(Expression
(N
));
7663 end Is_Name_Reference
;
7667 Loc
: constant Source_Ptr
:= Sloc
(Exp
);
7668 Exp_Type
: constant Entity_Id
:= Etype
(Exp
);
7669 Svg_Suppress
: constant Suppress_Record
:= Scope_Suppress
;
7673 Ptr_Typ_Decl
: Node_Id
;
7674 Ref_Type
: Entity_Id
;
7677 -- Start of processing for Remove_Side_Effects
7680 -- Handle cases in which there is nothing to do. In GNATprove mode,
7681 -- removal of side effects is useful for the light expansion of
7682 -- renamings. This removal should only occur when not inside a
7683 -- generic and not doing a pre-analysis.
7685 if not Expander_Active
7686 and (Inside_A_Generic
or not Full_Analysis
or not GNATprove_Mode
)
7691 -- Cannot generate temporaries if the invocation to remove side effects
7692 -- was issued too early and the type of the expression is not resolved
7693 -- (this happens because routines Duplicate_Subexpr_XX implicitly invoke
7694 -- Remove_Side_Effects).
7696 if No
(Exp_Type
) or else Ekind
(Exp_Type
) = E_Access_Attribute_Type
then
7699 -- No action needed for side-effect free expressions
7701 elsif Check_Side_Effects
7702 and then Side_Effect_Free
(Exp
, Name_Req
, Variable_Ref
)
7707 -- The remaining processing is done with all checks suppressed
7709 -- Note: from now on, don't use return statements, instead do a goto
7710 -- Leave, to ensure that we properly restore Scope_Suppress.Suppress.
7712 Scope_Suppress
.Suppress
:= (others => True);
7714 -- If this is an elementary or a small not by-reference record type, and
7715 -- we need to capture the value, just make a constant; this is cheap and
7716 -- objects of both kinds of types can be bit aligned, so it might not be
7717 -- possible to generate a reference to them. Likewise if this is not a
7718 -- name reference, except for a type conversion because we would enter
7719 -- an infinite recursion with Checks.Apply_Predicate_Check if the target
7720 -- type has predicates (and type conversions need a specific treatment
7721 -- anyway, see below). Also do it if we have a volatile reference and
7722 -- Name_Req is not set (see comments for Side_Effect_Free).
7724 if (Is_Elementary_Type
(Exp_Type
)
7725 or else (Is_Record_Type
(Exp_Type
)
7726 and then Known_Static_RM_Size
(Exp_Type
)
7727 and then RM_Size
(Exp_Type
) <= 64
7728 and then not Has_Discriminants
(Exp_Type
)
7729 and then not Is_By_Reference_Type
(Exp_Type
)))
7730 and then (Variable_Ref
7731 or else (not Is_Name_Reference
(Exp
)
7732 and then Nkind
(Exp
) /= N_Type_Conversion
)
7733 or else (not Name_Req
7734 and then Is_Volatile_Reference
(Exp
)))
7736 Def_Id
:= Build_Temporary
(Loc
, 'R', Exp
);
7737 Set_Etype
(Def_Id
, Exp_Type
);
7738 Res
:= New_Occurrence_Of
(Def_Id
, Loc
);
7740 -- If the expression is a packed reference, it must be reanalyzed and
7741 -- expanded, depending on context. This is the case for actuals where
7742 -- a constraint check may capture the actual before expansion of the
7743 -- call is complete.
7745 if Nkind
(Exp
) = N_Indexed_Component
7746 and then Is_Packed
(Etype
(Prefix
(Exp
)))
7748 Set_Analyzed
(Exp
, False);
7749 Set_Analyzed
(Prefix
(Exp
), False);
7753 -- Rnn : Exp_Type renames Expr;
7755 if Renaming_Req
then
7757 Make_Object_Renaming_Declaration
(Loc
,
7758 Defining_Identifier
=> Def_Id
,
7759 Subtype_Mark
=> New_Occurrence_Of
(Exp_Type
, Loc
),
7760 Name
=> Relocate_Node
(Exp
));
7763 -- Rnn : constant Exp_Type := Expr;
7767 Make_Object_Declaration
(Loc
,
7768 Defining_Identifier
=> Def_Id
,
7769 Object_Definition
=> New_Occurrence_Of
(Exp_Type
, Loc
),
7770 Constant_Present
=> True,
7771 Expression
=> Relocate_Node
(Exp
));
7773 Set_Assignment_OK
(E
);
7776 Insert_Action
(Exp
, E
);
7778 -- If the expression has the form v.all then we can just capture the
7779 -- pointer, and then do an explicit dereference on the result, but
7780 -- this is not right if this is a volatile reference.
7782 elsif Nkind
(Exp
) = N_Explicit_Dereference
7783 and then not Is_Volatile_Reference
(Exp
)
7785 Def_Id
:= Build_Temporary
(Loc
, 'R', Exp
);
7787 Make_Explicit_Dereference
(Loc
, New_Occurrence_Of
(Def_Id
, Loc
));
7790 Make_Object_Declaration
(Loc
,
7791 Defining_Identifier
=> Def_Id
,
7792 Object_Definition
=>
7793 New_Occurrence_Of
(Etype
(Prefix
(Exp
)), Loc
),
7794 Constant_Present
=> True,
7795 Expression
=> Relocate_Node
(Prefix
(Exp
))));
7797 -- Similar processing for an unchecked conversion of an expression of
7798 -- the form v.all, where we want the same kind of treatment.
7800 elsif Nkind
(Exp
) = N_Unchecked_Type_Conversion
7801 and then Nkind
(Expression
(Exp
)) = N_Explicit_Dereference
7803 Remove_Side_Effects
(Expression
(Exp
), Name_Req
, Variable_Ref
);
7806 -- If this is a type conversion, leave the type conversion and remove
7807 -- the side effects in the expression. This is important in several
7808 -- circumstances: for change of representations, and also when this is a
7809 -- view conversion to a smaller object, where gigi can end up creating
7810 -- its own temporary of the wrong size.
7812 elsif Nkind
(Exp
) = N_Type_Conversion
then
7813 Remove_Side_Effects
(Expression
(Exp
), Name_Req
, Variable_Ref
);
7815 -- Generating C code the type conversion of an access to constrained
7816 -- array type into an access to unconstrained array type involves
7817 -- initializing a fat pointer and the expression must be free of
7818 -- side effects to safely compute its bounds.
7821 and then Is_Access_Type
(Etype
(Exp
))
7822 and then Is_Array_Type
(Designated_Type
(Etype
(Exp
)))
7823 and then not Is_Constrained
(Designated_Type
(Etype
(Exp
)))
7825 Def_Id
:= Build_Temporary
(Loc
, 'R', Exp
);
7826 Set_Etype
(Def_Id
, Exp_Type
);
7827 Res
:= New_Occurrence_Of
(Def_Id
, Loc
);
7830 Make_Object_Declaration
(Loc
,
7831 Defining_Identifier
=> Def_Id
,
7832 Object_Definition
=> New_Occurrence_Of
(Exp_Type
, Loc
),
7833 Constant_Present
=> True,
7834 Expression
=> Relocate_Node
(Exp
)));
7839 -- If this is an unchecked conversion that Gigi can't handle, make
7840 -- a copy or a use a renaming to capture the value.
7842 elsif Nkind
(Exp
) = N_Unchecked_Type_Conversion
7843 and then not Safe_Unchecked_Type_Conversion
(Exp
)
7845 if CW_Or_Has_Controlled_Part
(Exp_Type
) then
7847 -- Use a renaming to capture the expression, rather than create
7848 -- a controlled temporary.
7850 Def_Id
:= Build_Temporary
(Loc
, 'R', Exp
);
7851 Res
:= New_Occurrence_Of
(Def_Id
, Loc
);
7854 Make_Object_Renaming_Declaration
(Loc
,
7855 Defining_Identifier
=> Def_Id
,
7856 Subtype_Mark
=> New_Occurrence_Of
(Exp_Type
, Loc
),
7857 Name
=> Relocate_Node
(Exp
)));
7860 Def_Id
:= Build_Temporary
(Loc
, 'R', Exp
);
7861 Set_Etype
(Def_Id
, Exp_Type
);
7862 Res
:= New_Occurrence_Of
(Def_Id
, Loc
);
7865 Make_Object_Declaration
(Loc
,
7866 Defining_Identifier
=> Def_Id
,
7867 Object_Definition
=> New_Occurrence_Of
(Exp_Type
, Loc
),
7868 Constant_Present
=> not Is_Variable
(Exp
),
7869 Expression
=> Relocate_Node
(Exp
));
7871 Set_Assignment_OK
(E
);
7872 Insert_Action
(Exp
, E
);
7875 -- For expressions that denote names, we can use a renaming scheme.
7876 -- This is needed for correctness in the case of a volatile object of
7877 -- a non-volatile type because the Make_Reference call of the "default"
7878 -- approach would generate an illegal access value (an access value
7879 -- cannot designate such an object - see Analyze_Reference).
7881 elsif Is_Name_Reference
(Exp
)
7883 -- We skip using this scheme if we have an object of a volatile
7884 -- type and we do not have Name_Req set true (see comments for
7885 -- Side_Effect_Free).
7887 and then (Name_Req
or else not Treat_As_Volatile
(Exp_Type
))
7889 Def_Id
:= Build_Temporary
(Loc
, 'R', Exp
);
7890 Res
:= New_Occurrence_Of
(Def_Id
, Loc
);
7893 Make_Object_Renaming_Declaration
(Loc
,
7894 Defining_Identifier
=> Def_Id
,
7895 Subtype_Mark
=> New_Occurrence_Of
(Exp_Type
, Loc
),
7896 Name
=> Relocate_Node
(Exp
)));
7898 -- If this is a packed reference, or a selected component with
7899 -- a non-standard representation, a reference to the temporary
7900 -- will be replaced by a copy of the original expression (see
7901 -- Exp_Ch2.Expand_Renaming). Otherwise the temporary must be
7902 -- elaborated by gigi, and is of course not to be replaced in-line
7903 -- by the expression it renames, which would defeat the purpose of
7904 -- removing the side-effect.
7906 if Nkind_In
(Exp
, N_Selected_Component
, N_Indexed_Component
)
7907 and then Has_Non_Standard_Rep
(Etype
(Prefix
(Exp
)))
7911 Set_Is_Renaming_Of_Object
(Def_Id
, False);
7914 -- Avoid generating a variable-sized temporary, by generating the
7915 -- reference just for the function call. The transformation could be
7916 -- refined to apply only when the array component is constrained by a
7919 elsif Nkind
(Exp
) = N_Selected_Component
7920 and then Nkind
(Prefix
(Exp
)) = N_Function_Call
7921 and then Is_Array_Type
(Exp_Type
)
7923 Remove_Side_Effects
(Prefix
(Exp
), Name_Req
, Variable_Ref
);
7926 -- Otherwise we generate a reference to the expression
7929 -- An expression which is in SPARK mode is considered side effect
7930 -- free if the resulting value is captured by a variable or a
7934 and then Nkind
(Parent
(Exp
)) = N_Object_Declaration
7938 -- When generating C code we cannot consider side effect free object
7939 -- declarations that have discriminants and are initialized by means
7940 -- of a function call since on this target there is no secondary
7941 -- stack to store the return value and the expander may generate an
7942 -- extra call to the function to compute the discriminant value. In
7943 -- addition, for targets that have secondary stack, the expansion of
7944 -- functions with side effects involves the generation of an access
7945 -- type to capture the return value stored in the secondary stack;
7946 -- by contrast when generating C code such expansion generates an
7947 -- internal object declaration (no access type involved) which must
7948 -- be identified here to avoid entering into a never-ending loop
7949 -- generating internal object declarations.
7951 elsif Generate_C_Code
7952 and then Nkind
(Parent
(Exp
)) = N_Object_Declaration
7954 (Nkind
(Exp
) /= N_Function_Call
7955 or else not Has_Discriminants
(Exp_Type
)
7956 or else Is_Internal_Name
7957 (Chars
(Defining_Identifier
(Parent
(Exp
)))))
7962 -- Special processing for function calls that return a limited type.
7963 -- We need to build a declaration that will enable build-in-place
7964 -- expansion of the call. This is not done if the context is already
7965 -- an object declaration, to prevent infinite recursion.
7967 -- This is relevant only in Ada 2005 mode. In Ada 95 programs we have
7968 -- to accommodate functions returning limited objects by reference.
7970 if Ada_Version
>= Ada_2005
7971 and then Nkind
(Exp
) = N_Function_Call
7972 and then Is_Limited_View
(Etype
(Exp
))
7973 and then Nkind
(Parent
(Exp
)) /= N_Object_Declaration
7976 Obj
: constant Entity_Id
:= Make_Temporary
(Loc
, 'F', Exp
);
7981 Make_Object_Declaration
(Loc
,
7982 Defining_Identifier
=> Obj
,
7983 Object_Definition
=> New_Occurrence_Of
(Exp_Type
, Loc
),
7984 Expression
=> Relocate_Node
(Exp
));
7986 Insert_Action
(Exp
, Decl
);
7987 Set_Etype
(Obj
, Exp_Type
);
7988 Rewrite
(Exp
, New_Occurrence_Of
(Obj
, Loc
));
7993 Def_Id
:= Build_Temporary
(Loc
, 'R', Exp
);
7995 -- The regular expansion of functions with side effects involves the
7996 -- generation of an access type to capture the return value found on
7997 -- the secondary stack. Since SPARK (and why) cannot process access
7998 -- types, use a different approach which ignores the secondary stack
7999 -- and "copies" the returned object.
8000 -- When generating C code, no need for a 'reference since the
8001 -- secondary stack is not supported.
8003 if GNATprove_Mode
or Generate_C_Code
then
8004 Res
:= New_Occurrence_Of
(Def_Id
, Loc
);
8005 Ref_Type
:= Exp_Type
;
8007 -- Regular expansion utilizing an access type and 'reference
8011 Make_Explicit_Dereference
(Loc
,
8012 Prefix
=> New_Occurrence_Of
(Def_Id
, Loc
));
8015 -- type Ann is access all <Exp_Type>;
8017 Ref_Type
:= Make_Temporary
(Loc
, 'A');
8020 Make_Full_Type_Declaration
(Loc
,
8021 Defining_Identifier
=> Ref_Type
,
8023 Make_Access_To_Object_Definition
(Loc
,
8024 All_Present
=> True,
8025 Subtype_Indication
=>
8026 New_Occurrence_Of
(Exp_Type
, Loc
)));
8028 Insert_Action
(Exp
, Ptr_Typ_Decl
);
8032 if Nkind
(E
) = N_Explicit_Dereference
then
8033 New_Exp
:= Relocate_Node
(Prefix
(E
));
8036 E
:= Relocate_Node
(E
);
8038 -- Do not generate a 'reference in SPARK mode or C generation
8039 -- since the access type is not created in the first place.
8041 if GNATprove_Mode
or Generate_C_Code
then
8044 -- Otherwise generate reference, marking the value as non-null
8045 -- since we know it cannot be null and we don't want a check.
8048 New_Exp
:= Make_Reference
(Loc
, E
);
8049 Set_Is_Known_Non_Null
(Def_Id
);
8053 if Is_Delayed_Aggregate
(E
) then
8055 -- The expansion of nested aggregates is delayed until the
8056 -- enclosing aggregate is expanded. As aggregates are often
8057 -- qualified, the predicate applies to qualified expressions as
8058 -- well, indicating that the enclosing aggregate has not been
8059 -- expanded yet. At this point the aggregate is part of a
8060 -- stand-alone declaration, and must be fully expanded.
8062 if Nkind
(E
) = N_Qualified_Expression
then
8063 Set_Expansion_Delayed
(Expression
(E
), False);
8064 Set_Analyzed
(Expression
(E
), False);
8066 Set_Expansion_Delayed
(E
, False);
8069 Set_Analyzed
(E
, False);
8072 -- Generating C code of object declarations that have discriminants
8073 -- and are initialized by means of a function call we propagate the
8074 -- discriminants of the parent type to the internally built object.
8075 -- This is needed to avoid generating an extra call to the called
8078 -- For example, if we generate here the following declaration, it
8079 -- will be expanded later adding an extra call to evaluate the value
8080 -- of the discriminant (needed to compute the size of the object).
8082 -- type Rec (D : Integer) is ...
8083 -- Obj : constant Rec := SomeFunc;
8086 and then Nkind
(Parent
(Exp
)) = N_Object_Declaration
8087 and then Has_Discriminants
(Exp_Type
)
8088 and then Nkind
(Exp
) = N_Function_Call
8091 Make_Object_Declaration
(Loc
,
8092 Defining_Identifier
=> Def_Id
,
8093 Object_Definition
=> New_Copy_Tree
8094 (Object_Definition
(Parent
(Exp
))),
8095 Constant_Present
=> True,
8096 Expression
=> New_Exp
));
8099 Make_Object_Declaration
(Loc
,
8100 Defining_Identifier
=> Def_Id
,
8101 Object_Definition
=> New_Occurrence_Of
(Ref_Type
, Loc
),
8102 Constant_Present
=> True,
8103 Expression
=> New_Exp
));
8107 -- Preserve the Assignment_OK flag in all copies, since at least one
8108 -- copy may be used in a context where this flag must be set (otherwise
8109 -- why would the flag be set in the first place).
8111 Set_Assignment_OK
(Res
, Assignment_OK
(Exp
));
8113 -- Finally rewrite the original expression and we are done
8116 Analyze_And_Resolve
(Exp
, Exp_Type
);
8119 Scope_Suppress
:= Svg_Suppress
;
8120 end Remove_Side_Effects
;
8122 ---------------------------
8123 -- Represented_As_Scalar --
8124 ---------------------------
8126 function Represented_As_Scalar
(T
: Entity_Id
) return Boolean is
8127 UT
: constant Entity_Id
:= Underlying_Type
(T
);
8129 return Is_Scalar_Type
(UT
)
8130 or else (Is_Bit_Packed_Array
(UT
)
8131 and then Is_Scalar_Type
(Packed_Array_Impl_Type
(UT
)));
8132 end Represented_As_Scalar
;
8134 ------------------------------
8135 -- Requires_Cleanup_Actions --
8136 ------------------------------
8138 function Requires_Cleanup_Actions
8140 Lib_Level
: Boolean) return Boolean
8142 At_Lib_Level
: constant Boolean :=
8144 and then Nkind_In
(N
, N_Package_Body
,
8145 N_Package_Specification
);
8146 -- N is at the library level if the top-most context is a package and
8147 -- the path taken to reach N does not inlcude non-package constructs.
8151 when N_Accept_Statement |
8159 Requires_Cleanup_Actions
(Declarations
(N
), At_Lib_Level
, True)
8161 (Present
(Handled_Statement_Sequence
(N
))
8163 Requires_Cleanup_Actions
8164 (Statements
(Handled_Statement_Sequence
(N
)),
8165 At_Lib_Level
, True));
8167 when N_Package_Specification
=>
8169 Requires_Cleanup_Actions
8170 (Visible_Declarations
(N
), At_Lib_Level
, True)
8172 Requires_Cleanup_Actions
8173 (Private_Declarations
(N
), At_Lib_Level
, True);
8178 end Requires_Cleanup_Actions
;
8180 ------------------------------
8181 -- Requires_Cleanup_Actions --
8182 ------------------------------
8184 function Requires_Cleanup_Actions
8186 Lib_Level
: Boolean;
8187 Nested_Constructs
: Boolean) return Boolean
8192 Obj_Typ
: Entity_Id
;
8193 Pack_Id
: Entity_Id
;
8198 or else Is_Empty_List
(L
)
8204 while Present
(Decl
) loop
8206 -- Library-level tagged types
8208 if Nkind
(Decl
) = N_Full_Type_Declaration
then
8209 Typ
:= Defining_Identifier
(Decl
);
8211 -- Ignored Ghost types do not need any cleanup actions because
8212 -- they will not appear in the final tree.
8214 if Is_Ignored_Ghost_Entity
(Typ
) then
8217 elsif Is_Tagged_Type
(Typ
)
8218 and then Is_Library_Level_Entity
(Typ
)
8219 and then Convention
(Typ
) = Convention_Ada
8220 and then Present
(Access_Disp_Table
(Typ
))
8221 and then RTE_Available
(RE_Unregister_Tag
)
8222 and then not Is_Abstract_Type
(Typ
)
8223 and then not No_Run_Time_Mode
8228 -- Regular object declarations
8230 elsif Nkind
(Decl
) = N_Object_Declaration
then
8231 Obj_Id
:= Defining_Identifier
(Decl
);
8232 Obj_Typ
:= Base_Type
(Etype
(Obj_Id
));
8233 Expr
:= Expression
(Decl
);
8235 -- Bypass any form of processing for objects which have their
8236 -- finalization disabled. This applies only to objects at the
8239 if Lib_Level
and then Finalize_Storage_Only
(Obj_Typ
) then
8242 -- Transient variables are treated separately in order to minimize
8243 -- the size of the generated code. See Exp_Ch7.Process_Transient_
8246 elsif Is_Processed_Transient
(Obj_Id
) then
8249 -- Ignored Ghost objects do not need any cleanup actions because
8250 -- they will not appear in the final tree.
8252 elsif Is_Ignored_Ghost_Entity
(Obj_Id
) then
8255 -- The expansion of iterator loops generates an object declaration
8256 -- where the Ekind is explicitly set to loop parameter. This is to
8257 -- ensure that the loop parameter behaves as a constant from user
8258 -- code point of view. Such object are never controlled and do not
8259 -- require cleanup actions. An iterator loop over a container of
8260 -- controlled objects does not produce such object declarations.
8262 elsif Ekind
(Obj_Id
) = E_Loop_Parameter
then
8265 -- The object is of the form:
8266 -- Obj : Typ [:= Expr];
8268 -- Do not process the incomplete view of a deferred constant. Do
8269 -- not consider tag-to-class-wide conversions.
8271 elsif not Is_Imported
(Obj_Id
)
8272 and then Needs_Finalization
(Obj_Typ
)
8273 and then not (Ekind
(Obj_Id
) = E_Constant
8274 and then not Has_Completion
(Obj_Id
))
8275 and then not Is_Tag_To_Class_Wide_Conversion
(Obj_Id
)
8279 -- The object is of the form:
8280 -- Obj : Access_Typ := Non_BIP_Function_Call'reference;
8282 -- Obj : Access_Typ :=
8283 -- BIP_Function_Call (BIPalloc => 2, ...)'reference;
8285 elsif Is_Access_Type
(Obj_Typ
)
8286 and then Needs_Finalization
8287 (Available_View
(Designated_Type
(Obj_Typ
)))
8288 and then Present
(Expr
)
8290 (Is_Secondary_Stack_BIP_Func_Call
(Expr
)
8292 (Is_Non_BIP_Func_Call
(Expr
)
8293 and then not Is_Related_To_Func_Return
(Obj_Id
)))
8297 -- Processing for "hook" objects generated for controlled
8298 -- transients declared inside an Expression_With_Actions.
8300 elsif Is_Access_Type
(Obj_Typ
)
8301 and then Present
(Status_Flag_Or_Transient_Decl
(Obj_Id
))
8302 and then Nkind
(Status_Flag_Or_Transient_Decl
(Obj_Id
)) =
8303 N_Object_Declaration
8307 -- Processing for intermediate results of if expressions where
8308 -- one of the alternatives uses a controlled function call.
8310 elsif Is_Access_Type
(Obj_Typ
)
8311 and then Present
(Status_Flag_Or_Transient_Decl
(Obj_Id
))
8312 and then Nkind
(Status_Flag_Or_Transient_Decl
(Obj_Id
)) =
8313 N_Defining_Identifier
8314 and then Present
(Expr
)
8315 and then Nkind
(Expr
) = N_Null
8319 -- Simple protected objects which use type System.Tasking.
8320 -- Protected_Objects.Protection to manage their locks should be
8321 -- treated as controlled since they require manual cleanup.
8323 elsif Ekind
(Obj_Id
) = E_Variable
8324 and then (Is_Simple_Protected_Type
(Obj_Typ
)
8325 or else Has_Simple_Protected_Object
(Obj_Typ
))
8330 -- Specific cases of object renamings
8332 elsif Nkind
(Decl
) = N_Object_Renaming_Declaration
then
8333 Obj_Id
:= Defining_Identifier
(Decl
);
8334 Obj_Typ
:= Base_Type
(Etype
(Obj_Id
));
8336 -- Bypass any form of processing for objects which have their
8337 -- finalization disabled. This applies only to objects at the
8340 if Lib_Level
and then Finalize_Storage_Only
(Obj_Typ
) then
8343 -- Ignored Ghost object renamings do not need any cleanup actions
8344 -- because they will not appear in the final tree.
8346 elsif Is_Ignored_Ghost_Entity
(Obj_Id
) then
8349 -- Return object of a build-in-place function. This case is
8350 -- recognized and marked by the expansion of an extended return
8351 -- statement (see Expand_N_Extended_Return_Statement).
8353 elsif Needs_Finalization
(Obj_Typ
)
8354 and then Is_Return_Object
(Obj_Id
)
8355 and then Present
(Status_Flag_Or_Transient_Decl
(Obj_Id
))
8359 -- Detect a case where a source object has been initialized by
8360 -- a controlled function call or another object which was later
8361 -- rewritten as a class-wide conversion of Ada.Tags.Displace.
8363 -- Obj1 : CW_Type := Src_Obj;
8364 -- Obj2 : CW_Type := Function_Call (...);
8366 -- Obj1 : CW_Type renames (... Ada.Tags.Displace (Src_Obj));
8367 -- Tmp : ... := Function_Call (...)'reference;
8368 -- Obj2 : CW_Type renames (... Ada.Tags.Displace (Tmp));
8370 elsif Is_Displacement_Of_Object_Or_Function_Result
(Obj_Id
) then
8374 -- Inspect the freeze node of an access-to-controlled type and look
8375 -- for a delayed finalization master. This case arises when the
8376 -- freeze actions are inserted at a later time than the expansion of
8377 -- the context. Since Build_Finalizer is never called on a single
8378 -- construct twice, the master will be ultimately left out and never
8379 -- finalized. This is also needed for freeze actions of designated
8380 -- types themselves, since in some cases the finalization master is
8381 -- associated with a designated type's freeze node rather than that
8382 -- of the access type (see handling for freeze actions in
8383 -- Build_Finalization_Master).
8385 elsif Nkind
(Decl
) = N_Freeze_Entity
8386 and then Present
(Actions
(Decl
))
8388 Typ
:= Entity
(Decl
);
8390 -- Freeze nodes for ignored Ghost types do not need cleanup
8391 -- actions because they will never appear in the final tree.
8393 if Is_Ignored_Ghost_Entity
(Typ
) then
8396 elsif ((Is_Access_Type
(Typ
)
8397 and then not Is_Access_Subprogram_Type
(Typ
)
8398 and then Needs_Finalization
8399 (Available_View
(Designated_Type
(Typ
))))
8400 or else (Is_Type
(Typ
) and then Needs_Finalization
(Typ
)))
8401 and then Requires_Cleanup_Actions
8402 (Actions
(Decl
), Lib_Level
, Nested_Constructs
)
8407 -- Nested package declarations
8409 elsif Nested_Constructs
8410 and then Nkind
(Decl
) = N_Package_Declaration
8412 Pack_Id
:= Defining_Entity
(Decl
);
8414 -- Do not inspect an ignored Ghost package because all code found
8415 -- within will not appear in the final tree.
8417 if Is_Ignored_Ghost_Entity
(Pack_Id
) then
8420 elsif Ekind
(Pack_Id
) /= E_Generic_Package
8421 and then Requires_Cleanup_Actions
8422 (Specification
(Decl
), Lib_Level
)
8427 -- Nested package bodies
8429 elsif Nested_Constructs
and then Nkind
(Decl
) = N_Package_Body
then
8431 -- Do not inspect an ignored Ghost package body because all code
8432 -- found within will not appear in the final tree.
8434 if Is_Ignored_Ghost_Entity
(Defining_Entity
(Decl
)) then
8437 elsif Ekind
(Corresponding_Spec
(Decl
)) /= E_Generic_Package
8438 and then Requires_Cleanup_Actions
(Decl
, Lib_Level
)
8443 elsif Nkind
(Decl
) = N_Block_Statement
8446 -- Handle a rare case caused by a controlled transient variable
8447 -- created as part of a record init proc. The variable is wrapped
8448 -- in a block, but the block is not associated with a transient
8453 -- Handle the case where the original context has been wrapped in
8454 -- a block to avoid interference between exception handlers and
8455 -- At_End handlers. Treat the block as transparent and process its
8458 or else Is_Finalization_Wrapper
(Decl
))
8460 if Requires_Cleanup_Actions
(Decl
, Lib_Level
) then
8469 end Requires_Cleanup_Actions
;
8471 ------------------------------------
8472 -- Safe_Unchecked_Type_Conversion --
8473 ------------------------------------
8475 -- Note: this function knows quite a bit about the exact requirements of
8476 -- Gigi with respect to unchecked type conversions, and its code must be
8477 -- coordinated with any changes in Gigi in this area.
8479 -- The above requirements should be documented in Sinfo ???
8481 function Safe_Unchecked_Type_Conversion
(Exp
: Node_Id
) return Boolean is
8486 Pexp
: constant Node_Id
:= Parent
(Exp
);
8489 -- If the expression is the RHS of an assignment or object declaration
8490 -- we are always OK because there will always be a target.
8492 -- Object renaming declarations, (generated for view conversions of
8493 -- actuals in inlined calls), like object declarations, provide an
8494 -- explicit type, and are safe as well.
8496 if (Nkind
(Pexp
) = N_Assignment_Statement
8497 and then Expression
(Pexp
) = Exp
)
8498 or else Nkind_In
(Pexp
, N_Object_Declaration
,
8499 N_Object_Renaming_Declaration
)
8503 -- If the expression is the prefix of an N_Selected_Component we should
8504 -- also be OK because GCC knows to look inside the conversion except if
8505 -- the type is discriminated. We assume that we are OK anyway if the
8506 -- type is not set yet or if it is controlled since we can't afford to
8507 -- introduce a temporary in this case.
8509 elsif Nkind
(Pexp
) = N_Selected_Component
8510 and then Prefix
(Pexp
) = Exp
8512 if No
(Etype
(Pexp
)) then
8516 not Has_Discriminants
(Etype
(Pexp
))
8517 or else Is_Constrained
(Etype
(Pexp
));
8521 -- Set the output type, this comes from Etype if it is set, otherwise we
8522 -- take it from the subtype mark, which we assume was already fully
8525 if Present
(Etype
(Exp
)) then
8526 Otyp
:= Etype
(Exp
);
8528 Otyp
:= Entity
(Subtype_Mark
(Exp
));
8531 -- The input type always comes from the expression, and we assume this
8532 -- is indeed always analyzed, so we can simply get the Etype.
8534 Ityp
:= Etype
(Expression
(Exp
));
8536 -- Initialize alignments to unknown so far
8541 -- Replace a concurrent type by its corresponding record type and each
8542 -- type by its underlying type and do the tests on those. The original
8543 -- type may be a private type whose completion is a concurrent type, so
8544 -- find the underlying type first.
8546 if Present
(Underlying_Type
(Otyp
)) then
8547 Otyp
:= Underlying_Type
(Otyp
);
8550 if Present
(Underlying_Type
(Ityp
)) then
8551 Ityp
:= Underlying_Type
(Ityp
);
8554 if Is_Concurrent_Type
(Otyp
) then
8555 Otyp
:= Corresponding_Record_Type
(Otyp
);
8558 if Is_Concurrent_Type
(Ityp
) then
8559 Ityp
:= Corresponding_Record_Type
(Ityp
);
8562 -- If the base types are the same, we know there is no problem since
8563 -- this conversion will be a noop.
8565 if Implementation_Base_Type
(Otyp
) = Implementation_Base_Type
(Ityp
) then
8568 -- Same if this is an upwards conversion of an untagged type, and there
8569 -- are no constraints involved (could be more general???)
8571 elsif Etype
(Ityp
) = Otyp
8572 and then not Is_Tagged_Type
(Ityp
)
8573 and then not Has_Discriminants
(Ityp
)
8574 and then No
(First_Rep_Item
(Base_Type
(Ityp
)))
8578 -- If the expression has an access type (object or subprogram) we assume
8579 -- that the conversion is safe, because the size of the target is safe,
8580 -- even if it is a record (which might be treated as having unknown size
8583 elsif Is_Access_Type
(Ityp
) then
8586 -- If the size of output type is known at compile time, there is never
8587 -- a problem. Note that unconstrained records are considered to be of
8588 -- known size, but we can't consider them that way here, because we are
8589 -- talking about the actual size of the object.
8591 -- We also make sure that in addition to the size being known, we do not
8592 -- have a case which might generate an embarrassingly large temp in
8593 -- stack checking mode.
8595 elsif Size_Known_At_Compile_Time
(Otyp
)
8597 (not Stack_Checking_Enabled
8598 or else not May_Generate_Large_Temp
(Otyp
))
8599 and then not (Is_Record_Type
(Otyp
) and then not Is_Constrained
(Otyp
))
8603 -- If either type is tagged, then we know the alignment is OK so Gigi
8604 -- will be able to use pointer punning.
8606 elsif Is_Tagged_Type
(Otyp
) or else Is_Tagged_Type
(Ityp
) then
8609 -- If either type is a limited record type, we cannot do a copy, so say
8610 -- safe since there's nothing else we can do.
8612 elsif Is_Limited_Record
(Otyp
) or else Is_Limited_Record
(Ityp
) then
8615 -- Conversions to and from packed array types are always ignored and
8618 elsif Is_Packed_Array_Impl_Type
(Otyp
)
8619 or else Is_Packed_Array_Impl_Type
(Ityp
)
8624 -- The only other cases known to be safe is if the input type's
8625 -- alignment is known to be at least the maximum alignment for the
8626 -- target or if both alignments are known and the output type's
8627 -- alignment is no stricter than the input's. We can use the component
8628 -- type alignement for an array if a type is an unpacked array type.
8630 if Present
(Alignment_Clause
(Otyp
)) then
8631 Oalign
:= Expr_Value
(Expression
(Alignment_Clause
(Otyp
)));
8633 elsif Is_Array_Type
(Otyp
)
8634 and then Present
(Alignment_Clause
(Component_Type
(Otyp
)))
8636 Oalign
:= Expr_Value
(Expression
(Alignment_Clause
8637 (Component_Type
(Otyp
))));
8640 if Present
(Alignment_Clause
(Ityp
)) then
8641 Ialign
:= Expr_Value
(Expression
(Alignment_Clause
(Ityp
)));
8643 elsif Is_Array_Type
(Ityp
)
8644 and then Present
(Alignment_Clause
(Component_Type
(Ityp
)))
8646 Ialign
:= Expr_Value
(Expression
(Alignment_Clause
8647 (Component_Type
(Ityp
))));
8650 if Ialign
/= No_Uint
and then Ialign
> Maximum_Alignment
then
8653 elsif Ialign
/= No_Uint
8654 and then Oalign
/= No_Uint
8655 and then Ialign
<= Oalign
8659 -- Otherwise, Gigi cannot handle this and we must make a temporary
8664 end Safe_Unchecked_Type_Conversion
;
8666 ---------------------------------
8667 -- Set_Current_Value_Condition --
8668 ---------------------------------
8670 -- Note: the implementation of this procedure is very closely tied to the
8671 -- implementation of Get_Current_Value_Condition. Here we set required
8672 -- Current_Value fields, and in Get_Current_Value_Condition, we interpret
8673 -- them, so they must have a consistent view.
8675 procedure Set_Current_Value_Condition
(Cnode
: Node_Id
) is
8677 procedure Set_Entity_Current_Value
(N
: Node_Id
);
8678 -- If N is an entity reference, where the entity is of an appropriate
8679 -- kind, then set the current value of this entity to Cnode, unless
8680 -- there is already a definite value set there.
8682 procedure Set_Expression_Current_Value
(N
: Node_Id
);
8683 -- If N is of an appropriate form, sets an appropriate entry in current
8684 -- value fields of relevant entities. Multiple entities can be affected
8685 -- in the case of an AND or AND THEN.
8687 ------------------------------
8688 -- Set_Entity_Current_Value --
8689 ------------------------------
8691 procedure Set_Entity_Current_Value
(N
: Node_Id
) is
8693 if Is_Entity_Name
(N
) then
8695 Ent
: constant Entity_Id
:= Entity
(N
);
8698 -- Don't capture if not safe to do so
8700 if not Safe_To_Capture_Value
(N
, Ent
, Cond
=> True) then
8704 -- Here we have a case where the Current_Value field may need
8705 -- to be set. We set it if it is not already set to a compile
8706 -- time expression value.
8708 -- Note that this represents a decision that one condition
8709 -- blots out another previous one. That's certainly right if
8710 -- they occur at the same level. If the second one is nested,
8711 -- then the decision is neither right nor wrong (it would be
8712 -- equally OK to leave the outer one in place, or take the new
8713 -- inner one. Really we should record both, but our data
8714 -- structures are not that elaborate.
8716 if Nkind
(Current_Value
(Ent
)) not in N_Subexpr
then
8717 Set_Current_Value
(Ent
, Cnode
);
8721 end Set_Entity_Current_Value
;
8723 ----------------------------------
8724 -- Set_Expression_Current_Value --
8725 ----------------------------------
8727 procedure Set_Expression_Current_Value
(N
: Node_Id
) is
8733 -- Loop to deal with (ignore for now) any NOT operators present. The
8734 -- presence of NOT operators will be handled properly when we call
8735 -- Get_Current_Value_Condition.
8737 while Nkind
(Cond
) = N_Op_Not
loop
8738 Cond
:= Right_Opnd
(Cond
);
8741 -- For an AND or AND THEN, recursively process operands
8743 if Nkind
(Cond
) = N_Op_And
or else Nkind
(Cond
) = N_And_Then
then
8744 Set_Expression_Current_Value
(Left_Opnd
(Cond
));
8745 Set_Expression_Current_Value
(Right_Opnd
(Cond
));
8749 -- Check possible relational operator
8751 if Nkind
(Cond
) in N_Op_Compare
then
8752 if Compile_Time_Known_Value
(Right_Opnd
(Cond
)) then
8753 Set_Entity_Current_Value
(Left_Opnd
(Cond
));
8754 elsif Compile_Time_Known_Value
(Left_Opnd
(Cond
)) then
8755 Set_Entity_Current_Value
(Right_Opnd
(Cond
));
8758 elsif Nkind_In
(Cond
,
8760 N_Qualified_Expression
,
8761 N_Expression_With_Actions
)
8763 Set_Expression_Current_Value
(Expression
(Cond
));
8765 -- Check possible boolean variable reference
8768 Set_Entity_Current_Value
(Cond
);
8770 end Set_Expression_Current_Value
;
8772 -- Start of processing for Set_Current_Value_Condition
8775 Set_Expression_Current_Value
(Condition
(Cnode
));
8776 end Set_Current_Value_Condition
;
8778 --------------------------
8779 -- Set_Elaboration_Flag --
8780 --------------------------
8782 procedure Set_Elaboration_Flag
(N
: Node_Id
; Spec_Id
: Entity_Id
) is
8783 Loc
: constant Source_Ptr
:= Sloc
(N
);
8784 Ent
: constant Entity_Id
:= Elaboration_Entity
(Spec_Id
);
8788 if Present
(Ent
) then
8790 -- Nothing to do if at the compilation unit level, because in this
8791 -- case the flag is set by the binder generated elaboration routine.
8793 if Nkind
(Parent
(N
)) = N_Compilation_Unit
then
8796 -- Here we do need to generate an assignment statement
8799 Check_Restriction
(No_Elaboration_Code
, N
);
8801 Make_Assignment_Statement
(Loc
,
8802 Name
=> New_Occurrence_Of
(Ent
, Loc
),
8803 Expression
=> Make_Integer_Literal
(Loc
, Uint_1
));
8805 if Nkind
(Parent
(N
)) = N_Subunit
then
8806 Insert_After
(Corresponding_Stub
(Parent
(N
)), Asn
);
8808 Insert_After
(N
, Asn
);
8813 -- Kill current value indication. This is necessary because the
8814 -- tests of this flag are inserted out of sequence and must not
8815 -- pick up bogus indications of the wrong constant value.
8817 Set_Current_Value
(Ent
, Empty
);
8819 -- If the subprogram is in the current declarative part and
8820 -- 'access has been applied to it, generate an elaboration
8821 -- check at the beginning of the declarations of the body.
8823 if Nkind
(N
) = N_Subprogram_Body
8824 and then Address_Taken
(Spec_Id
)
8826 Ekind_In
(Scope
(Spec_Id
), E_Block
, E_Procedure
, E_Function
)
8829 Loc
: constant Source_Ptr
:= Sloc
(N
);
8830 Decls
: constant List_Id
:= Declarations
(N
);
8834 -- No need to generate this check if first entry in the
8835 -- declaration list is a raise of Program_Error now.
8838 and then Nkind
(First
(Decls
)) = N_Raise_Program_Error
8843 -- Otherwise generate the check
8846 Make_Raise_Program_Error
(Loc
,
8849 Left_Opnd
=> New_Occurrence_Of
(Ent
, Loc
),
8850 Right_Opnd
=> Make_Integer_Literal
(Loc
, Uint_0
)),
8851 Reason
=> PE_Access_Before_Elaboration
);
8854 Set_Declarations
(N
, New_List
(Chk
));
8856 Prepend
(Chk
, Decls
);
8864 end Set_Elaboration_Flag
;
8866 ----------------------------
8867 -- Set_Renamed_Subprogram --
8868 ----------------------------
8870 procedure Set_Renamed_Subprogram
(N
: Node_Id
; E
: Entity_Id
) is
8872 -- If input node is an identifier, we can just reset it
8874 if Nkind
(N
) = N_Identifier
then
8875 Set_Chars
(N
, Chars
(E
));
8878 -- Otherwise we have to do a rewrite, preserving Comes_From_Source
8882 CS
: constant Boolean := Comes_From_Source
(N
);
8884 Rewrite
(N
, Make_Identifier
(Sloc
(N
), Chars
(E
)));
8886 Set_Comes_From_Source
(N
, CS
);
8887 Set_Analyzed
(N
, True);
8890 end Set_Renamed_Subprogram
;
8892 ----------------------
8893 -- Side_Effect_Free --
8894 ----------------------
8896 function Side_Effect_Free
8898 Name_Req
: Boolean := False;
8899 Variable_Ref
: Boolean := False) return Boolean
8901 Typ
: constant Entity_Id
:= Etype
(N
);
8902 -- Result type of the expression
8904 function Safe_Prefixed_Reference
(N
: Node_Id
) return Boolean;
8905 -- The argument N is a construct where the Prefix is dereferenced if it
8906 -- is an access type and the result is a variable. The call returns True
8907 -- if the construct is side effect free (not considering side effects in
8908 -- other than the prefix which are to be tested by the caller).
8910 function Within_In_Parameter
(N
: Node_Id
) return Boolean;
8911 -- Determines if N is a subcomponent of a composite in-parameter. If so,
8912 -- N is not side-effect free when the actual is global and modifiable
8913 -- indirectly from within a subprogram, because it may be passed by
8914 -- reference. The front-end must be conservative here and assume that
8915 -- this may happen with any array or record type. On the other hand, we
8916 -- cannot create temporaries for all expressions for which this
8917 -- condition is true, for various reasons that might require clearing up
8918 -- ??? For example, discriminant references that appear out of place, or
8919 -- spurious type errors with class-wide expressions. As a result, we
8920 -- limit the transformation to loop bounds, which is so far the only
8921 -- case that requires it.
8923 -----------------------------
8924 -- Safe_Prefixed_Reference --
8925 -----------------------------
8927 function Safe_Prefixed_Reference
(N
: Node_Id
) return Boolean is
8929 -- If prefix is not side effect free, definitely not safe
8931 if not Side_Effect_Free
(Prefix
(N
), Name_Req
, Variable_Ref
) then
8934 -- If the prefix is of an access type that is not access-to-constant,
8935 -- then this construct is a variable reference, which means it is to
8936 -- be considered to have side effects if Variable_Ref is set True.
8938 elsif Is_Access_Type
(Etype
(Prefix
(N
)))
8939 and then not Is_Access_Constant
(Etype
(Prefix
(N
)))
8940 and then Variable_Ref
8942 -- Exception is a prefix that is the result of a previous removal
8945 return Is_Entity_Name
(Prefix
(N
))
8946 and then not Comes_From_Source
(Prefix
(N
))
8947 and then Ekind
(Entity
(Prefix
(N
))) = E_Constant
8948 and then Is_Internal_Name
(Chars
(Entity
(Prefix
(N
))));
8950 -- If the prefix is an explicit dereference then this construct is a
8951 -- variable reference, which means it is to be considered to have
8952 -- side effects if Variable_Ref is True.
8954 -- We do NOT exclude dereferences of access-to-constant types because
8955 -- we handle them as constant view of variables.
8957 elsif Nkind
(Prefix
(N
)) = N_Explicit_Dereference
8958 and then Variable_Ref
8962 -- Note: The following test is the simplest way of solving a complex
8963 -- problem uncovered by the following test (Side effect on loop bound
8964 -- that is a subcomponent of a global variable:
8966 -- with Text_Io; use Text_Io;
8967 -- procedure Tloop is
8970 -- V : Natural := 4;
8971 -- S : String (1..5) := (others => 'a');
8978 -- with procedure Action;
8979 -- procedure Loop_G (Arg : X; Msg : String)
8981 -- procedure Loop_G (Arg : X; Msg : String) is
8983 -- Put_Line ("begin loop_g " & Msg & " will loop till: "
8984 -- & Natural'Image (Arg.V));
8985 -- for Index in 1 .. Arg.V loop
8987 -- (Natural'Image (Index) & " " & Arg.S (Index));
8988 -- if Index > 2 then
8992 -- Put_Line ("end loop_g " & Msg);
8995 -- procedure Loop1 is new Loop_G (Modi);
8996 -- procedure Modi is
8999 -- Loop1 (X1, "from modi");
9003 -- Loop1 (X1, "initial");
9006 -- The output of the above program should be:
9008 -- begin loop_g initial will loop till: 4
9012 -- begin loop_g from modi will loop till: 1
9014 -- end loop_g from modi
9016 -- begin loop_g from modi will loop till: 1
9018 -- end loop_g from modi
9019 -- end loop_g initial
9021 -- If a loop bound is a subcomponent of a global variable, a
9022 -- modification of that variable within the loop may incorrectly
9023 -- affect the execution of the loop.
9025 elsif Nkind
(Parent
(Parent
(N
))) = N_Loop_Parameter_Specification
9026 and then Within_In_Parameter
(Prefix
(N
))
9027 and then Variable_Ref
9031 -- All other cases are side effect free
9036 end Safe_Prefixed_Reference
;
9038 -------------------------
9039 -- Within_In_Parameter --
9040 -------------------------
9042 function Within_In_Parameter
(N
: Node_Id
) return Boolean is
9044 if not Comes_From_Source
(N
) then
9047 elsif Is_Entity_Name
(N
) then
9048 return Ekind
(Entity
(N
)) = E_In_Parameter
;
9050 elsif Nkind_In
(N
, N_Indexed_Component
, N_Selected_Component
) then
9051 return Within_In_Parameter
(Prefix
(N
));
9056 end Within_In_Parameter
;
9058 -- Start of processing for Side_Effect_Free
9061 -- If volatile reference, always consider it to have side effects
9063 if Is_Volatile_Reference
(N
) then
9067 -- Note on checks that could raise Constraint_Error. Strictly, if we
9068 -- take advantage of 11.6, these checks do not count as side effects.
9069 -- However, we would prefer to consider that they are side effects,
9070 -- since the backend CSE does not work very well on expressions which
9071 -- can raise Constraint_Error. On the other hand if we don't consider
9072 -- them to be side effect free, then we get some awkward expansions
9073 -- in -gnato mode, resulting in code insertions at a point where we
9074 -- do not have a clear model for performing the insertions.
9076 -- Special handling for entity names
9078 if Is_Entity_Name
(N
) then
9080 -- A type reference is always side effect free
9082 if Is_Type
(Entity
(N
)) then
9085 -- Variables are considered to be a side effect if Variable_Ref
9086 -- is set or if we have a volatile reference and Name_Req is off.
9087 -- If Name_Req is True then we can't help returning a name which
9088 -- effectively allows multiple references in any case.
9090 elsif Is_Variable
(N
, Use_Original_Node
=> False) then
9091 return not Variable_Ref
9092 and then (not Is_Volatile_Reference
(N
) or else Name_Req
);
9094 -- Any other entity (e.g. a subtype name) is definitely side
9101 -- A value known at compile time is always side effect free
9103 elsif Compile_Time_Known_Value
(N
) then
9106 -- A variable renaming is not side-effect free, because the renaming
9107 -- will function like a macro in the front-end in some cases, and an
9108 -- assignment can modify the component designated by N, so we need to
9109 -- create a temporary for it.
9111 -- The guard testing for Entity being present is needed at least in
9112 -- the case of rewritten predicate expressions, and may well also be
9113 -- appropriate elsewhere. Obviously we can't go testing the entity
9114 -- field if it does not exist, so it's reasonable to say that this is
9115 -- not the renaming case if it does not exist.
9117 elsif Is_Entity_Name
(Original_Node
(N
))
9118 and then Present
(Entity
(Original_Node
(N
)))
9119 and then Is_Renaming_Of_Object
(Entity
(Original_Node
(N
)))
9120 and then Ekind
(Entity
(Original_Node
(N
))) /= E_Constant
9123 RO
: constant Node_Id
:=
9124 Renamed_Object
(Entity
(Original_Node
(N
)));
9127 -- If the renamed object is an indexed component, or an
9128 -- explicit dereference, then the designated object could
9129 -- be modified by an assignment.
9131 if Nkind_In
(RO
, N_Indexed_Component
,
9132 N_Explicit_Dereference
)
9136 -- A selected component must have a safe prefix
9138 elsif Nkind
(RO
) = N_Selected_Component
then
9139 return Safe_Prefixed_Reference
(RO
);
9141 -- In all other cases, designated object cannot be changed so
9142 -- we are side effect free.
9149 -- Remove_Side_Effects generates an object renaming declaration to
9150 -- capture the expression of a class-wide expression. In VM targets
9151 -- the frontend performs no expansion for dispatching calls to
9152 -- class- wide types since they are handled by the VM. Hence, we must
9153 -- locate here if this node corresponds to a previous invocation of
9154 -- Remove_Side_Effects to avoid a never ending loop in the frontend.
9156 elsif not Tagged_Type_Expansion
9157 and then not Comes_From_Source
(N
)
9158 and then Nkind
(Parent
(N
)) = N_Object_Renaming_Declaration
9159 and then Is_Class_Wide_Type
(Typ
)
9163 -- Generating C the type conversion of an access to constrained array
9164 -- type into an access to unconstrained array type involves initializing
9165 -- a fat pointer and the expression cannot be assumed to be free of side
9166 -- effects since it must referenced several times to compute its bounds.
9168 elsif Generate_C_Code
9169 and then Nkind
(N
) = N_Type_Conversion
9170 and then Is_Access_Type
(Typ
)
9171 and then Is_Array_Type
(Designated_Type
(Typ
))
9172 and then not Is_Constrained
(Designated_Type
(Typ
))
9177 -- For other than entity names and compile time known values,
9178 -- check the node kind for special processing.
9182 -- An attribute reference is side effect free if its expressions
9183 -- are side effect free and its prefix is side effect free or
9184 -- is an entity reference.
9186 -- Is this right? what about x'first where x is a variable???
9188 when N_Attribute_Reference
=>
9189 return Side_Effect_Free
(Expressions
(N
), Name_Req
, Variable_Ref
)
9190 and then Attribute_Name
(N
) /= Name_Input
9191 and then (Is_Entity_Name
(Prefix
(N
))
9192 or else Side_Effect_Free
9193 (Prefix
(N
), Name_Req
, Variable_Ref
));
9195 -- A binary operator is side effect free if and both operands are
9196 -- side effect free. For this purpose binary operators include
9197 -- membership tests and short circuit forms.
9199 when N_Binary_Op | N_Membership_Test | N_Short_Circuit
=>
9200 return Side_Effect_Free
(Left_Opnd
(N
), Name_Req
, Variable_Ref
)
9202 Side_Effect_Free
(Right_Opnd
(N
), Name_Req
, Variable_Ref
);
9204 -- An explicit dereference is side effect free only if it is
9205 -- a side effect free prefixed reference.
9207 when N_Explicit_Dereference
=>
9208 return Safe_Prefixed_Reference
(N
);
9210 -- An expression with action is side effect free if its expression
9211 -- is side effect free and it has no actions.
9213 when N_Expression_With_Actions
=>
9214 return Is_Empty_List
(Actions
(N
))
9216 Side_Effect_Free
(Expression
(N
), Name_Req
, Variable_Ref
);
9218 -- A call to _rep_to_pos is side effect free, since we generate
9219 -- this pure function call ourselves. Moreover it is critically
9220 -- important to make this exception, since otherwise we can have
9221 -- discriminants in array components which don't look side effect
9222 -- free in the case of an array whose index type is an enumeration
9223 -- type with an enumeration rep clause.
9225 -- All other function calls are not side effect free
9227 when N_Function_Call
=>
9228 return Nkind
(Name
(N
)) = N_Identifier
9229 and then Is_TSS
(Name
(N
), TSS_Rep_To_Pos
)
9232 (First
(Parameter_Associations
(N
)), Name_Req
, Variable_Ref
);
9234 -- An IF expression is side effect free if it's of a scalar type, and
9235 -- all its components are all side effect free (conditions and then
9236 -- actions and else actions). We restrict to scalar types, since it
9237 -- is annoying to deal with things like (if A then B else C)'First
9238 -- where the type involved is a string type.
9240 when N_If_Expression
=>
9241 return Is_Scalar_Type
(Typ
)
9243 Side_Effect_Free
(Expressions
(N
), Name_Req
, Variable_Ref
);
9245 -- An indexed component is side effect free if it is a side
9246 -- effect free prefixed reference and all the indexing
9247 -- expressions are side effect free.
9249 when N_Indexed_Component
=>
9250 return Side_Effect_Free
(Expressions
(N
), Name_Req
, Variable_Ref
)
9251 and then Safe_Prefixed_Reference
(N
);
9253 -- A type qualification is side effect free if the expression
9254 -- is side effect free.
9256 when N_Qualified_Expression
=>
9257 return Side_Effect_Free
(Expression
(N
), Name_Req
, Variable_Ref
);
9259 -- A selected component is side effect free only if it is a side
9260 -- effect free prefixed reference.
9262 when N_Selected_Component
=>
9263 return Safe_Prefixed_Reference
(N
);
9265 -- A range is side effect free if the bounds are side effect free
9268 return Side_Effect_Free
(Low_Bound
(N
), Name_Req
, Variable_Ref
)
9270 Side_Effect_Free
(High_Bound
(N
), Name_Req
, Variable_Ref
);
9272 -- A slice is side effect free if it is a side effect free
9273 -- prefixed reference and the bounds are side effect free.
9276 return Side_Effect_Free
9277 (Discrete_Range
(N
), Name_Req
, Variable_Ref
)
9278 and then Safe_Prefixed_Reference
(N
);
9280 -- A type conversion is side effect free if the expression to be
9281 -- converted is side effect free.
9283 when N_Type_Conversion
=>
9284 return Side_Effect_Free
(Expression
(N
), Name_Req
, Variable_Ref
);
9286 -- A unary operator is side effect free if the operand
9287 -- is side effect free.
9290 return Side_Effect_Free
(Right_Opnd
(N
), Name_Req
, Variable_Ref
);
9292 -- An unchecked type conversion is side effect free only if it
9293 -- is safe and its argument is side effect free.
9295 when N_Unchecked_Type_Conversion
=>
9296 return Safe_Unchecked_Type_Conversion
(N
)
9298 Side_Effect_Free
(Expression
(N
), Name_Req
, Variable_Ref
);
9300 -- An unchecked expression is side effect free if its expression
9301 -- is side effect free.
9303 when N_Unchecked_Expression
=>
9304 return Side_Effect_Free
(Expression
(N
), Name_Req
, Variable_Ref
);
9306 -- A literal is side effect free
9308 when N_Character_Literal |
9314 -- We consider that anything else has side effects. This is a bit
9315 -- crude, but we are pretty close for most common cases, and we
9316 -- are certainly correct (i.e. we never return True when the
9317 -- answer should be False).
9322 end Side_Effect_Free
;
9324 -- A list is side effect free if all elements of the list are side
9327 function Side_Effect_Free
9329 Name_Req
: Boolean := False;
9330 Variable_Ref
: Boolean := False) return Boolean
9335 if L
= No_List
or else L
= Error_List
then
9340 while Present
(N
) loop
9341 if not Side_Effect_Free
(N
, Name_Req
, Variable_Ref
) then
9350 end Side_Effect_Free
;
9352 ----------------------------------
9353 -- Silly_Boolean_Array_Not_Test --
9354 ----------------------------------
9356 -- This procedure implements an odd and silly test. We explicitly check
9357 -- for the case where the 'First of the component type is equal to the
9358 -- 'Last of this component type, and if this is the case, we make sure
9359 -- that constraint error is raised. The reason is that the NOT is bound
9360 -- to cause CE in this case, and we will not otherwise catch it.
9362 -- No such check is required for AND and OR, since for both these cases
9363 -- False op False = False, and True op True = True. For the XOR case,
9364 -- see Silly_Boolean_Array_Xor_Test.
9366 -- Believe it or not, this was reported as a bug. Note that nearly always,
9367 -- the test will evaluate statically to False, so the code will be
9368 -- statically removed, and no extra overhead caused.
9370 procedure Silly_Boolean_Array_Not_Test
(N
: Node_Id
; T
: Entity_Id
) is
9371 Loc
: constant Source_Ptr
:= Sloc
(N
);
9372 CT
: constant Entity_Id
:= Component_Type
(T
);
9375 -- The check we install is
9377 -- constraint_error when
9378 -- component_type'first = component_type'last
9379 -- and then array_type'Length /= 0)
9381 -- We need the last guard because we don't want to raise CE for empty
9382 -- arrays since no out of range values result. (Empty arrays with a
9383 -- component type of True .. True -- very useful -- even the ACATS
9384 -- does not test that marginal case).
9387 Make_Raise_Constraint_Error
(Loc
,
9393 Make_Attribute_Reference
(Loc
,
9394 Prefix
=> New_Occurrence_Of
(CT
, Loc
),
9395 Attribute_Name
=> Name_First
),
9398 Make_Attribute_Reference
(Loc
,
9399 Prefix
=> New_Occurrence_Of
(CT
, Loc
),
9400 Attribute_Name
=> Name_Last
)),
9402 Right_Opnd
=> Make_Non_Empty_Check
(Loc
, Right_Opnd
(N
))),
9403 Reason
=> CE_Range_Check_Failed
));
9404 end Silly_Boolean_Array_Not_Test
;
9406 ----------------------------------
9407 -- Silly_Boolean_Array_Xor_Test --
9408 ----------------------------------
9410 -- This procedure implements an odd and silly test. We explicitly check
9411 -- for the XOR case where the component type is True .. True, since this
9412 -- will raise constraint error. A special check is required since CE
9413 -- will not be generated otherwise (cf Expand_Packed_Not).
9415 -- No such check is required for AND and OR, since for both these cases
9416 -- False op False = False, and True op True = True, and no check is
9417 -- required for the case of False .. False, since False xor False = False.
9418 -- See also Silly_Boolean_Array_Not_Test
9420 procedure Silly_Boolean_Array_Xor_Test
(N
: Node_Id
; T
: Entity_Id
) is
9421 Loc
: constant Source_Ptr
:= Sloc
(N
);
9422 CT
: constant Entity_Id
:= Component_Type
(T
);
9425 -- The check we install is
9427 -- constraint_error when
9428 -- Boolean (component_type'First)
9429 -- and then Boolean (component_type'Last)
9430 -- and then array_type'Length /= 0)
9432 -- We need the last guard because we don't want to raise CE for empty
9433 -- arrays since no out of range values result (Empty arrays with a
9434 -- component type of True .. True -- very useful -- even the ACATS
9435 -- does not test that marginal case).
9438 Make_Raise_Constraint_Error
(Loc
,
9444 Convert_To
(Standard_Boolean
,
9445 Make_Attribute_Reference
(Loc
,
9446 Prefix
=> New_Occurrence_Of
(CT
, Loc
),
9447 Attribute_Name
=> Name_First
)),
9450 Convert_To
(Standard_Boolean
,
9451 Make_Attribute_Reference
(Loc
,
9452 Prefix
=> New_Occurrence_Of
(CT
, Loc
),
9453 Attribute_Name
=> Name_Last
))),
9455 Right_Opnd
=> Make_Non_Empty_Check
(Loc
, Right_Opnd
(N
))),
9456 Reason
=> CE_Range_Check_Failed
));
9457 end Silly_Boolean_Array_Xor_Test
;
9459 --------------------------
9460 -- Target_Has_Fixed_Ops --
9461 --------------------------
9463 Integer_Sized_Small
: Ureal
;
9464 -- Set to 2.0 ** -(Integer'Size - 1) the first time that this function is
9465 -- called (we don't want to compute it more than once).
9467 Long_Integer_Sized_Small
: Ureal
;
9468 -- Set to 2.0 ** -(Long_Integer'Size - 1) the first time that this function
9469 -- is called (we don't want to compute it more than once)
9471 First_Time_For_THFO
: Boolean := True;
9472 -- Set to False after first call (if Fractional_Fixed_Ops_On_Target)
9474 function Target_Has_Fixed_Ops
9475 (Left_Typ
: Entity_Id
;
9476 Right_Typ
: Entity_Id
;
9477 Result_Typ
: Entity_Id
) return Boolean
9479 function Is_Fractional_Type
(Typ
: Entity_Id
) return Boolean;
9480 -- Return True if the given type is a fixed-point type with a small
9481 -- value equal to 2 ** (-(T'Object_Size - 1)) and whose values have
9482 -- an absolute value less than 1.0. This is currently limited to
9483 -- fixed-point types that map to Integer or Long_Integer.
9485 ------------------------
9486 -- Is_Fractional_Type --
9487 ------------------------
9489 function Is_Fractional_Type
(Typ
: Entity_Id
) return Boolean is
9491 if Esize
(Typ
) = Standard_Integer_Size
then
9492 return Small_Value
(Typ
) = Integer_Sized_Small
;
9494 elsif Esize
(Typ
) = Standard_Long_Integer_Size
then
9495 return Small_Value
(Typ
) = Long_Integer_Sized_Small
;
9500 end Is_Fractional_Type
;
9502 -- Start of processing for Target_Has_Fixed_Ops
9505 -- Return False if Fractional_Fixed_Ops_On_Target is false
9507 if not Fractional_Fixed_Ops_On_Target
then
9511 -- Here the target has Fractional_Fixed_Ops, if first time, compute
9512 -- standard constants used by Is_Fractional_Type.
9514 if First_Time_For_THFO
then
9515 First_Time_For_THFO
:= False;
9517 Integer_Sized_Small
:=
9520 Den
=> UI_From_Int
(Standard_Integer_Size
- 1),
9523 Long_Integer_Sized_Small
:=
9526 Den
=> UI_From_Int
(Standard_Long_Integer_Size
- 1),
9530 -- Return True if target supports fixed-by-fixed multiply/divide for
9531 -- fractional fixed-point types (see Is_Fractional_Type) and the operand
9532 -- and result types are equivalent fractional types.
9534 return Is_Fractional_Type
(Base_Type
(Left_Typ
))
9535 and then Is_Fractional_Type
(Base_Type
(Right_Typ
))
9536 and then Is_Fractional_Type
(Base_Type
(Result_Typ
))
9537 and then Esize
(Left_Typ
) = Esize
(Right_Typ
)
9538 and then Esize
(Left_Typ
) = Esize
(Result_Typ
);
9539 end Target_Has_Fixed_Ops
;
9541 ------------------------------------------
9542 -- Type_May_Have_Bit_Aligned_Components --
9543 ------------------------------------------
9545 function Type_May_Have_Bit_Aligned_Components
9546 (Typ
: Entity_Id
) return Boolean
9549 -- Array type, check component type
9551 if Is_Array_Type
(Typ
) then
9553 Type_May_Have_Bit_Aligned_Components
(Component_Type
(Typ
));
9555 -- Record type, check components
9557 elsif Is_Record_Type
(Typ
) then
9562 E
:= First_Component_Or_Discriminant
(Typ
);
9563 while Present
(E
) loop
9564 if Component_May_Be_Bit_Aligned
(E
)
9565 or else Type_May_Have_Bit_Aligned_Components
(Etype
(E
))
9570 Next_Component_Or_Discriminant
(E
);
9576 -- Type other than array or record is always OK
9581 end Type_May_Have_Bit_Aligned_Components
;
9583 ----------------------------------
9584 -- Within_Case_Or_If_Expression --
9585 ----------------------------------
9587 function Within_Case_Or_If_Expression
(N
: Node_Id
) return Boolean is
9591 -- Locate an enclosing case or if expression. Note that these constructs
9592 -- can be expanded into Expression_With_Actions, hence the test of the
9596 while Present
(Par
) loop
9597 if Nkind_In
(Original_Node
(Par
), N_Case_Expression
,
9602 -- Prevent the search from going too far
9604 elsif Is_Body_Or_Package_Declaration
(Par
) then
9608 Par
:= Parent
(Par
);
9612 end Within_Case_Or_If_Expression
;
9614 --------------------------------
9615 -- Within_Internal_Subprogram --
9616 --------------------------------
9618 function Within_Internal_Subprogram
return Boolean is
9623 while Present
(S
) and then not Is_Subprogram
(S
) loop
9628 and then Get_TSS_Name
(S
) /= TSS_Null
9629 and then not Is_Predicate_Function
(S
)
9630 and then not Is_Predicate_Function_M
(S
);
9631 end Within_Internal_Subprogram
;