1 ------------------------------------------------------------------------------
3 -- GNAT COMPILER COMPONENTS --
9 -- Copyright (C) 1992-2023, 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 Checks
; use Checks
;
29 with Debug
; use Debug
;
30 with Einfo
; use Einfo
;
31 with Einfo
.Entities
; use Einfo
.Entities
;
32 with Einfo
.Utils
; use Einfo
.Utils
;
33 with Elists
; use Elists
;
34 with Errout
; use Errout
;
35 with Expander
; use Expander
;
36 with Exp_Util
; use Exp_Util
;
37 with Exp_Ch3
; use Exp_Ch3
;
38 with Exp_Ch6
; use Exp_Ch6
;
39 with Exp_Ch7
; use Exp_Ch7
;
40 with Exp_Ch9
; use Exp_Ch9
;
41 with Exp_Disp
; use Exp_Disp
;
42 with Exp_Tss
; use Exp_Tss
;
43 with Freeze
; use Freeze
;
44 with Itypes
; use Itypes
;
46 with Namet
; use Namet
;
47 with Nmake
; use Nmake
;
48 with Nlists
; use Nlists
;
50 with Restrict
; use Restrict
;
51 with Rident
; use Rident
;
52 with Rtsfind
; use Rtsfind
;
53 with Ttypes
; use Ttypes
;
55 with Sem_Aggr
; use Sem_Aggr
;
56 with Sem_Aux
; use Sem_Aux
;
57 with Sem_Case
; use Sem_Case
;
58 with Sem_Ch3
; use Sem_Ch3
;
59 with Sem_Ch8
; use Sem_Ch8
;
60 with Sem_Ch13
; use Sem_Ch13
;
61 with Sem_Eval
; use Sem_Eval
;
62 with Sem_Mech
; use Sem_Mech
;
63 with Sem_Res
; use Sem_Res
;
64 with Sem_Util
; use Sem_Util
;
65 use Sem_Util
.Storage_Model_Support
;
66 with Sinfo
; use Sinfo
;
67 with Sinfo
.Nodes
; use Sinfo
.Nodes
;
68 with Sinfo
.Utils
; use Sinfo
.Utils
;
69 with Snames
; use Snames
;
70 with Stand
; use Stand
;
71 with Stringt
; use Stringt
;
72 with Tbuild
; use Tbuild
;
73 with Uintp
; use Uintp
;
74 with Urealp
; use Urealp
;
75 with Warnsw
; use Warnsw
;
77 package body Exp_Aggr
is
79 function Build_Assignment_With_Temporary
82 Source
: Node_Id
) return List_Id
;
83 -- Returns a list of actions to assign Source to Target of type Typ using
84 -- an extra temporary, which can potentially be large.
86 type Case_Bounds
is record
89 Choice_Node
: Node_Id
;
92 type Case_Table_Type
is array (Nat
range <>) of Case_Bounds
;
93 -- Table type used by Check_Case_Choices procedure
95 procedure Expand_Delta_Array_Aggregate
(N
: Node_Id
; Deltas
: List_Id
);
96 procedure Expand_Delta_Record_Aggregate
(N
: Node_Id
; Deltas
: List_Id
);
97 procedure Expand_Container_Aggregate
(N
: Node_Id
);
99 function Get_Base_Object
(N
: Node_Id
) return Entity_Id
;
100 -- Return the base object, i.e. the outermost prefix object, that N refers
101 -- to statically, or Empty if it cannot be determined. The assumption is
102 -- that all dereferences are explicit in the tree rooted at N.
104 function Has_Default_Init_Comps
(N
: Node_Id
) return Boolean;
105 -- N is an aggregate (record or array). Checks the presence of default
106 -- initialization (<>) in any component (Ada 2005: AI-287).
108 function Is_CCG_Supported_Aggregate
(N
: Node_Id
) return Boolean;
109 -- Return True if aggregate N is located in a context supported by the
110 -- CCG backend; False otherwise.
112 function Is_Static_Dispatch_Table_Aggregate
(N
: Node_Id
) return Boolean;
113 -- Returns true if N is an aggregate used to initialize the components
114 -- of a statically allocated dispatch table.
116 function Late_Expansion
119 Target
: Node_Id
) return List_Id
;
120 -- This routine implements top-down expansion of nested aggregates. In
121 -- doing so, it avoids the generation of temporaries at each level. N is
122 -- a nested record or array aggregate with the Expansion_Delayed flag.
123 -- Typ is the expected type of the aggregate. Target is a (duplicatable)
124 -- expression that will hold the result of the aggregate expansion.
126 function Make_OK_Assignment_Statement
129 Expression
: Node_Id
) return Node_Id
;
130 -- This is like Make_Assignment_Statement, except that Assignment_OK
131 -- is set in the left operand. All assignments built by this unit use
132 -- this routine. This is needed to deal with assignments to initialized
133 -- constants that are done in place.
137 Obj_Type
: Entity_Id
;
138 Typ
: Entity_Id
) return Boolean;
139 -- A static array aggregate in an object declaration can in most cases be
140 -- expanded in place. The one exception is when the aggregate is given
141 -- with component associations that specify different bounds from those of
142 -- the type definition in the object declaration. In this pathological
143 -- case the aggregate must slide, and we must introduce an intermediate
144 -- temporary to hold it.
146 -- The same holds in an assignment to one-dimensional array of arrays,
147 -- when a component may be given with bounds that differ from those of the
150 function Number_Of_Choices
(N
: Node_Id
) return Nat
;
151 -- Returns the number of discrete choices (not including the others choice
152 -- if present) contained in (sub-)aggregate N.
154 procedure Process_Transient_Component
156 Comp_Typ
: Entity_Id
;
158 Fin_Call
: out Node_Id
;
159 Hook_Clear
: out Node_Id
;
160 Aggr
: Node_Id
:= Empty
;
161 Stmts
: List_Id
:= No_List
);
162 -- Subsidiary to the expansion of array and record aggregates. Generate
163 -- part of the necessary code to finalize a transient component. Comp_Typ
164 -- is the component type. Init_Expr is the initialization expression of the
165 -- component which is always a function call. Fin_Call is the finalization
166 -- call used to clean up the transient function result. Hook_Clear is the
167 -- hook reset statement. Aggr and Stmts both control the placement of the
168 -- generated code. Aggr is the related aggregate. If present, all code is
169 -- inserted prior to Aggr using Insert_Action. Stmts is the initialization
170 -- statements of the component. If present, all code is added to Stmts.
172 procedure Process_Transient_Component_Completion
176 Hook_Clear
: Node_Id
;
178 -- Subsidiary to the expansion of array and record aggregates. Generate
179 -- part of the necessary code to finalize a transient component. Aggr is
180 -- the related aggregate. Fin_Clear is the finalization call used to clean
181 -- up the transient component. Hook_Clear is the hook reset statement.
182 -- Stmts is the initialization statement list for the component. All
183 -- generated code is added to Stmts.
185 procedure Sort_Case_Table
(Case_Table
: in out Case_Table_Type
);
186 -- Sort the Case Table using the Lower Bound of each Choice as the key.
187 -- A simple insertion sort is used since the number of choices in a case
188 -- statement of variant part will usually be small and probably in near
191 ------------------------------------------------------
192 -- Local subprograms for Record Aggregate Expansion --
193 ------------------------------------------------------
195 function Is_Build_In_Place_Aggregate_Return
(N
: Node_Id
) return Boolean;
196 -- True if N is an aggregate (possibly qualified or converted) that is
197 -- being returned from a build-in-place function.
199 function Build_Record_Aggr_Code
202 Lhs
: Node_Id
) return List_Id
;
203 -- N is an N_Aggregate or an N_Extension_Aggregate. Typ is the type of the
204 -- aggregate. Target is an expression containing the location on which the
205 -- component by component assignments will take place. Returns the list of
206 -- assignments plus all other adjustments needed for tagged and controlled
209 procedure Convert_To_Assignments
(N
: Node_Id
; Typ
: Entity_Id
);
210 -- Transform a record aggregate into a sequence of assignments performed
211 -- component by component. N is an N_Aggregate or N_Extension_Aggregate.
212 -- Typ is the type of the record aggregate.
214 procedure Expand_Record_Aggregate
216 Orig_Tag
: Node_Id
:= Empty
;
217 Parent_Expr
: Node_Id
:= Empty
);
218 -- This is the top level procedure for record aggregate expansion.
219 -- Expansion for record aggregates needs expand aggregates for tagged
220 -- record types. Specifically Expand_Record_Aggregate adds the Tag
221 -- field in front of the Component_Association list that was created
222 -- during resolution by Resolve_Record_Aggregate.
224 -- N is the record aggregate node.
225 -- Orig_Tag is the value of the Tag that has to be provided for this
226 -- specific aggregate. It carries the tag corresponding to the type
227 -- of the outermost aggregate during the recursive expansion
228 -- Parent_Expr is the ancestor part of the original extension
231 function Has_Mutable_Components
(Typ
: Entity_Id
) return Boolean;
232 -- Return true if one of the components is of a discriminated type with
233 -- defaults. An aggregate for a type with mutable components must be
234 -- expanded into individual assignments.
236 function In_Place_Assign_OK
238 Target_Object
: Entity_Id
:= Empty
) return Boolean;
239 -- Predicate to determine whether an aggregate assignment can be done in
240 -- place, because none of the new values can depend on the components of
241 -- the target of the assignment.
243 procedure Initialize_Discriminants
(N
: Node_Id
; Typ
: Entity_Id
);
244 -- If the type of the aggregate is a type extension with renamed discrimi-
245 -- nants, we must initialize the hidden discriminants of the parent.
246 -- Otherwise, the target object must not be initialized. The discriminants
247 -- are initialized by calling the initialization procedure for the type.
248 -- This is incorrect if the initialization of other components has any
249 -- side effects. We restrict this call to the case where the parent type
250 -- has a variant part, because this is the only case where the hidden
251 -- discriminants are accessed, namely when calling discriminant checking
252 -- functions of the parent type, and when applying a stream attribute to
253 -- an object of the derived type.
255 -----------------------------------------------------
256 -- Local Subprograms for Array Aggregate Expansion --
257 -----------------------------------------------------
259 function Aggr_Assignment_OK_For_Backend
(N
: Node_Id
) return Boolean;
260 -- Returns true if an aggregate assignment can be done by the back end
262 function Aggr_Size_OK
(N
: Node_Id
) return Boolean;
263 -- Very large static aggregates present problems to the back-end, and are
264 -- transformed into assignments and loops. This function verifies that the
265 -- total number of components of an aggregate is acceptable for rewriting
266 -- into a purely positional static form. Aggr_Size_OK must be called before
269 -- This function also detects and warns about one-component aggregates that
270 -- appear in a nonstatic context. Even if the component value is static,
271 -- such an aggregate must be expanded into an assignment.
273 function Backend_Processing_Possible
(N
: Node_Id
) return Boolean;
274 -- This function checks if array aggregate N can be processed directly
275 -- by the backend. If this is the case, True is returned.
277 function Build_Array_Aggr_Code
282 Scalar_Comp
: Boolean;
283 Indexes
: List_Id
:= No_List
) return List_Id
;
284 -- This recursive routine returns a list of statements containing the
285 -- loops and assignments that are needed for the expansion of the array
288 -- N is the (sub-)aggregate node to be expanded into code. This node has
289 -- been fully analyzed, and its Etype is properly set.
291 -- Index is the index node corresponding to the array subaggregate N
293 -- Into is the target expression into which we are copying the aggregate.
294 -- Note that this node may not have been analyzed yet, and so the Etype
295 -- field may not be set.
297 -- Scalar_Comp is True if the component type of the aggregate is scalar
299 -- Indexes is the current list of expressions used to index the object we
302 procedure Convert_Array_Aggr_In_Allocator
306 -- If the aggregate appears within an allocator and can be expanded in
307 -- place, this routine generates the individual assignments to components
308 -- of the designated object. This is an optimization over the general
309 -- case, where a temporary is first created on the stack and then used to
310 -- construct the allocated object on the heap.
312 procedure Convert_To_Positional
314 Handle_Bit_Packed
: Boolean := False);
315 -- If possible, convert named notation to positional notation. This
316 -- conversion is possible only in some static cases. If the conversion is
317 -- possible, then N is rewritten with the analyzed converted aggregate.
318 -- The parameter Handle_Bit_Packed is usually set False (since we do
319 -- not expect the back end to handle bit packed arrays, so the normal case
320 -- of conversion is pointless), but in the special case of a call from
321 -- Packed_Array_Aggregate_Handled, we set this parameter to True, since
322 -- these are cases we handle in there.
324 procedure Expand_Array_Aggregate
(N
: Node_Id
);
325 -- This is the top-level routine to perform array aggregate expansion.
326 -- N is the N_Aggregate node to be expanded.
328 function Is_Two_Dim_Packed_Array
(Typ
: Entity_Id
) return Boolean;
329 -- For two-dimensional packed aggregates with constant bounds and constant
330 -- components, it is preferable to pack the inner aggregates because the
331 -- whole matrix can then be presented to the back-end as a one-dimensional
332 -- list of literals. This is much more efficient than expanding into single
333 -- component assignments. This function determines if the type Typ is for
334 -- an array that is suitable for this optimization: it returns True if Typ
335 -- is a two dimensional bit packed array with component size 1, 2, or 4.
337 function Max_Aggregate_Size
339 Default_Size
: Nat
:= 5000) return Nat
;
340 -- Return the max size for a static aggregate N. Return Default_Size if no
341 -- other special criteria trigger.
343 function Packed_Array_Aggregate_Handled
(N
: Node_Id
) return Boolean;
344 -- Given an array aggregate, this function handles the case of a packed
345 -- array aggregate with all constant values, where the aggregate can be
346 -- evaluated at compile time. If this is possible, then N is rewritten
347 -- to be its proper compile time value with all the components properly
348 -- assembled. The expression is analyzed and resolved and True is returned.
349 -- If this transformation is not possible, N is unchanged and False is
352 function Two_Dim_Packed_Array_Handled
(N
: Node_Id
) return Boolean;
353 -- If the type of the aggregate is a two-dimensional bit_packed array
354 -- it may be transformed into an array of bytes with constant values,
355 -- and presented to the back-end as a static value. The function returns
356 -- false if this transformation cannot be performed. THis is similar to,
357 -- and reuses part of the machinery in Packed_Array_Aggregate_Handled.
359 ------------------------------------
360 -- Aggr_Assignment_OK_For_Backend --
361 ------------------------------------
363 -- Back-end processing by Gigi/gcc is possible only if all the following
364 -- conditions are met:
366 -- 1. N consists of a single OTHERS choice, possibly recursively, or
367 -- of a single choice, possibly recursively, if it is surrounded by
368 -- a qualified expression whose subtype mark is unconstrained.
370 -- 2. The array type has no null ranges (the purpose of this is to
371 -- avoid a bogus warning for an out-of-range value).
373 -- 3. The array type has no atomic components
375 -- 4. The component type is elementary
377 -- 5. The component size is a multiple of Storage_Unit
379 -- 6. The component size is Storage_Unit or the value is of the form
380 -- M * (1 + A**1 + A**2 + .. A**(K-1)) where A = 2**(Storage_Unit)
381 -- and M in 0 .. A-1. This can also be viewed as K occurrences of
382 -- the Storage_Unit value M, concatenated together.
384 -- The ultimate goal is to generate a call to a fast memset routine
385 -- specifically optimized for the target.
387 function Aggr_Assignment_OK_For_Backend
(N
: Node_Id
) return Boolean is
389 function Is_OK_Aggregate
(Aggr
: Node_Id
) return Boolean;
390 -- Return true if Aggr is suitable for back-end assignment
392 ---------------------
393 -- Is_OK_Aggregate --
394 ---------------------
396 function Is_OK_Aggregate
(Aggr
: Node_Id
) return Boolean is
397 Assoc
: constant List_Id
:= Component_Associations
(Aggr
);
400 -- An "others" aggregate is most likely OK, but see below
402 if Is_Others_Aggregate
(Aggr
) then
405 -- An aggregate with a single choice requires a qualified expression
406 -- whose subtype mark is an unconstrained type because we need it to
407 -- have the semantics of an "others" aggregate.
409 elsif Nkind
(Parent
(N
)) = N_Qualified_Expression
410 and then not Is_Constrained
(Entity
(Subtype_Mark
(Parent
(N
))))
411 and then Is_Single_Aggregate
(Aggr
)
415 -- The other cases are not OK
421 -- In any case we do not support an iterated association
423 return Nkind
(First
(Assoc
)) /= N_Iterated_Component_Association
;
426 Bounds
: Range_Nodes
;
427 Csiz
: Uint
:= No_Uint
;
435 -- Start of processing for Aggr_Assignment_OK_For_Backend
438 -- Back end doesn't know about <>
440 if Has_Default_Init_Comps
(N
) then
444 -- Recurse as far as possible to find the innermost component type
448 while Is_Array_Type
(Ctyp
) loop
449 if Nkind
(Expr
) /= N_Aggregate
450 or else not Is_OK_Aggregate
(Expr
)
455 Index
:= First_Index
(Ctyp
);
456 while Present
(Index
) loop
457 Bounds
:= Get_Index_Bounds
(Index
);
459 if Is_Null_Range
(Bounds
.First
, Bounds
.Last
) then
466 Expr
:= Expression
(First
(Component_Associations
(Expr
)));
468 for J
in 1 .. Number_Dimensions
(Ctyp
) - 1 loop
469 if Nkind
(Expr
) /= N_Aggregate
470 or else not Is_OK_Aggregate
(Expr
)
475 Expr
:= Expression
(First
(Component_Associations
(Expr
)));
478 if Has_Atomic_Components
(Ctyp
) then
482 Csiz
:= Component_Size
(Ctyp
);
483 Ctyp
:= Component_Type
(Ctyp
);
485 if Is_Full_Access
(Ctyp
) then
490 -- Access types need to be dealt with specially
492 if Is_Access_Type
(Ctyp
) then
494 -- Component_Size is not set by Layout_Type if the component
495 -- type is an access type ???
497 Csiz
:= Esize
(Ctyp
);
499 -- Fat pointers are rejected as they are not really elementary
502 if No
(Csiz
) or else Csiz
/= System_Address_Size
then
506 -- The supported expressions are NULL and constants, others are
507 -- rejected upfront to avoid being analyzed below, which can be
508 -- problematic for some of them, for example allocators.
510 if Nkind
(Expr
) /= N_Null
and then not Is_Entity_Name
(Expr
) then
514 -- Scalar types are OK if their size is a multiple of Storage_Unit
516 elsif Is_Scalar_Type
(Ctyp
) and then Present
(Csiz
) then
518 if Csiz
mod System_Storage_Unit
/= 0 then
522 -- Composite types are rejected
528 -- If the expression has side effects (e.g. contains calls with
529 -- potential side effects) reject as well. We only preanalyze the
530 -- expression to prevent the removal of intended side effects.
532 Preanalyze_And_Resolve
(Expr
, Ctyp
);
534 if not Side_Effect_Free
(Expr
) then
538 -- The expression needs to be analyzed if True is returned
540 Analyze_And_Resolve
(Expr
, Ctyp
);
542 -- Strip away any conversions from the expression as they simply
543 -- qualify the real expression.
545 while Nkind
(Expr
) in N_Unchecked_Type_Conversion | N_Type_Conversion
547 Expr
:= Expression
(Expr
);
550 Nunits
:= UI_To_Int
(Csiz
) / System_Storage_Unit
;
556 if not Compile_Time_Known_Value
(Expr
) then
560 -- The only supported value for floating point is 0.0
562 if Is_Floating_Point_Type
(Ctyp
) then
563 return Expr_Value_R
(Expr
) = Ureal_0
;
566 -- For other types, we can look into the value as an integer, which
567 -- means the representation value for enumeration literals.
569 Value
:= Expr_Rep_Value
(Expr
);
571 if Has_Biased_Representation
(Ctyp
) then
572 Value
:= Value
- Expr_Value
(Type_Low_Bound
(Ctyp
));
575 -- Values 0 and -1 immediately satisfy the last check
577 if Value
= Uint_0
or else Value
= Uint_Minus_1
then
581 -- We need to work with an unsigned value
584 Value
:= Value
+ 2**(System_Storage_Unit
* Nunits
);
587 Remainder
:= Value
rem 2**System_Storage_Unit
;
589 for J
in 1 .. Nunits
- 1 loop
590 Value
:= Value
/ 2**System_Storage_Unit
;
592 if Value
rem 2**System_Storage_Unit
/= Remainder
then
598 end Aggr_Assignment_OK_For_Backend
;
604 function Aggr_Size_OK
(N
: Node_Id
) return Boolean is
605 Typ
: constant Entity_Id
:= Etype
(N
);
614 -- Determines the maximum size of an array aggregate produced by
615 -- converting named to positional notation (e.g. from others clauses).
616 -- This avoids running away with attempts to convert huge aggregates,
617 -- which hit memory limits in the backend.
619 function Component_Count
(T
: Entity_Id
) return Nat
;
620 -- The limit is applied to the total number of subcomponents that the
621 -- aggregate will have, which is the number of static expressions
622 -- that will appear in the flattened array. This requires a recursive
623 -- computation of the number of scalar components of the structure.
625 ---------------------
626 -- Component_Count --
627 ---------------------
629 function Component_Count
(T
: Entity_Id
) return Nat
is
634 if Is_Scalar_Type
(T
) then
637 elsif Is_Record_Type
(T
) then
638 Comp
:= First_Component
(T
);
639 while Present
(Comp
) loop
640 Res
:= Res
+ Component_Count
(Etype
(Comp
));
641 Next_Component
(Comp
);
646 elsif Is_Array_Type
(T
) then
648 Lo
: constant Node_Id
:=
649 Type_Low_Bound
(Etype
(First_Index
(T
)));
650 Hi
: constant Node_Id
:=
651 Type_High_Bound
(Etype
(First_Index
(T
)));
653 Siz
: constant Nat
:= Component_Count
(Component_Type
(T
));
656 -- Check for superflat arrays, i.e. arrays with such bounds
657 -- as 4 .. 2, to insure that this function never returns a
658 -- meaningless negative value.
660 if not Compile_Time_Known_Value
(Lo
)
661 or else not Compile_Time_Known_Value
(Hi
)
662 or else Expr_Value
(Hi
) < Expr_Value
(Lo
)
667 -- If the number of components is greater than Int'Last,
668 -- then return Int'Last, so caller will return False (Aggr
669 -- size is not OK). Otherwise, UI_To_Int will crash.
672 UI
: constant Uint
:=
673 (Expr_Value
(Hi
) - Expr_Value
(Lo
) + 1) * Siz
;
675 if UI_Is_In_Int_Range
(UI
) then
676 return UI_To_Int
(UI
);
685 -- Can only be a null for an access type
691 -- Start of processing for Aggr_Size_OK
694 -- We bump the maximum size unless the aggregate has a single component
695 -- association, which will be more efficient if implemented with a loop.
696 -- The -gnatd_g switch disables this bumping.
698 if (No
(Expressions
(N
))
699 and then No
(Next
(First
(Component_Associations
(N
)))))
700 or else Debug_Flag_Underscore_G
702 Max_Aggr_Size
:= Max_Aggregate_Size
(N
);
704 Max_Aggr_Size
:= Max_Aggregate_Size
(N
, 500_000
);
707 Size
:= UI_From_Int
(Component_Count
(Component_Type
(Typ
)));
709 Indx
:= First_Index
(Typ
);
710 while Present
(Indx
) loop
711 Lo
:= Type_Low_Bound
(Etype
(Indx
));
712 Hi
:= Type_High_Bound
(Etype
(Indx
));
714 -- Bounds need to be known at compile time
716 if not Compile_Time_Known_Value
(Lo
)
717 or else not Compile_Time_Known_Value
(Hi
)
722 Lov
:= Expr_Value
(Lo
);
723 Hiv
:= Expr_Value
(Hi
);
725 -- A flat array is always safe
731 -- One-component aggregates are suspicious, and if the context type
732 -- is an object declaration with nonstatic bounds it will trip gcc;
733 -- such an aggregate must be expanded into a single assignment.
735 if Hiv
= Lov
and then Nkind
(Parent
(N
)) = N_Object_Declaration
then
737 Index_Type
: constant Entity_Id
:=
739 (First_Index
(Etype
(Defining_Identifier
(Parent
(N
)))));
743 if not Compile_Time_Known_Value
(Type_Low_Bound
(Index_Type
))
744 or else not Compile_Time_Known_Value
745 (Type_High_Bound
(Index_Type
))
747 if Present
(Component_Associations
(N
)) then
750 (Choice_List
(First
(Component_Associations
(N
))));
752 if Is_Entity_Name
(Indx
)
753 and then not Is_Type
(Entity
(Indx
))
756 ("single component aggregate in "
757 & "non-static context??", Indx
);
758 Error_Msg_N
("\maybe subtype name was meant??", Indx
);
768 Rng
: constant Uint
:= Hiv
- Lov
+ 1;
771 -- Check if size is too large
773 if not UI_Is_In_Int_Range
(Rng
) then
777 -- Compute the size using universal arithmetic to avoid the
778 -- possibility of overflow on very large aggregates.
783 or else Size
> Max_Aggr_Size
789 -- Bounds must be in integer range, for later array construction
791 if not UI_Is_In_Int_Range
(Lov
)
793 not UI_Is_In_Int_Range
(Hiv
)
804 ---------------------------------
805 -- Backend_Processing_Possible --
806 ---------------------------------
808 -- Backend processing by Gigi/gcc is possible only if all the following
809 -- conditions are met:
811 -- 1. N is fully positional
813 -- 2. N is not a bit-packed array aggregate;
815 -- 3. The size of N's array type must be known at compile time. Note
816 -- that this implies that the component size is also known
818 -- 4. The array type of N does not follow the Fortran layout convention
819 -- or if it does it must be 1 dimensional.
821 -- 5. The array component type may not be tagged (which could necessitate
822 -- reassignment of proper tags).
824 -- 6. The array component type must not have unaligned bit components
826 -- 7. None of the components of the aggregate may be bit unaligned
829 -- 8. There cannot be delayed components, since we do not know enough
830 -- at this stage to know if back end processing is possible.
832 -- 9. There cannot be any discriminated record components, since the
833 -- back end cannot handle this complex case.
835 -- 10. No controlled actions need to be generated for components
837 -- 11. When generating C code, N must be part of a N_Object_Declaration
839 -- 12. When generating C code, N must not include function calls
841 function Backend_Processing_Possible
(N
: Node_Id
) return Boolean is
842 Typ
: constant Entity_Id
:= Etype
(N
);
843 -- Typ is the correct constrained array subtype of the aggregate
845 function Component_Check
(N
: Node_Id
; Index
: Node_Id
) return Boolean;
846 -- This routine checks components of aggregate N, enforcing checks
847 -- 1, 7, 8, 9, 11, and 12. In the multidimensional case, these checks
848 -- are performed on subaggregates. The Index value is the current index
849 -- being checked in the multidimensional case.
851 ---------------------
852 -- Component_Check --
853 ---------------------
855 function Component_Check
(N
: Node_Id
; Index
: Node_Id
) return Boolean is
856 function Ultimate_Original_Expression
(N
: Node_Id
) return Node_Id
;
857 -- Given a type conversion or an unchecked type conversion N, return
858 -- its innermost original expression.
860 ----------------------------------
861 -- Ultimate_Original_Expression --
862 ----------------------------------
864 function Ultimate_Original_Expression
(N
: Node_Id
) return Node_Id
is
865 Expr
: Node_Id
:= Original_Node
(N
);
868 while Nkind
(Expr
) in
869 N_Type_Conversion | N_Unchecked_Type_Conversion
871 Expr
:= Original_Node
(Expression
(Expr
));
875 end Ultimate_Original_Expression
;
881 -- Start of processing for Component_Check
884 -- Checks 1: (no component associations)
886 if Present
(Component_Associations
(N
)) then
890 -- Checks 11: The C code generator cannot handle aggregates that are
891 -- not part of an object declaration.
893 if Modify_Tree_For_C
and then not Is_CCG_Supported_Aggregate
(N
) then
897 -- Checks on components
899 -- Recurse to check subaggregates, which may appear in qualified
900 -- expressions. If delayed, the front-end will have to expand.
901 -- If the component is a discriminated record, treat as nonstatic,
902 -- as the back-end cannot handle this properly.
904 Expr
:= First
(Expressions
(N
));
905 while Present
(Expr
) loop
907 -- Checks 8: (no delayed components)
909 if Is_Delayed_Aggregate
(Expr
) then
913 -- Checks 9: (no discriminated records)
915 if Present
(Etype
(Expr
))
916 and then Is_Record_Type
(Etype
(Expr
))
917 and then Has_Discriminants
(Etype
(Expr
))
922 -- Checks 7. Component must not be bit aligned component
924 if Possible_Bit_Aligned_Component
(Expr
) then
928 -- Checks 12: (no function call)
932 Nkind
(Ultimate_Original_Expression
(Expr
)) = N_Function_Call
937 -- Recursion to following indexes for multiple dimension case
939 if Present
(Next_Index
(Index
))
940 and then not Component_Check
(Expr
, Next_Index
(Index
))
945 -- All checks for that component finished, on to next
953 -- Start of processing for Backend_Processing_Possible
956 -- Checks 2 (array not bit packed) and 10 (no controlled actions)
958 if Is_Bit_Packed_Array
(Typ
) or else Needs_Finalization
(Typ
) then
962 -- If component is limited, aggregate must be expanded because each
963 -- component assignment must be built in place.
965 if Is_Limited_View
(Component_Type
(Typ
)) then
969 -- Checks 4 (array must not be multidimensional Fortran case)
971 if Convention
(Typ
) = Convention_Fortran
972 and then Number_Dimensions
(Typ
) > 1
977 -- Checks 3 (size of array must be known at compile time)
979 if not Size_Known_At_Compile_Time
(Typ
) then
983 -- Checks on components
985 if not Component_Check
(N
, First_Index
(Typ
)) then
989 -- Checks 5 (if the component type is tagged, then we may need to do
990 -- tag adjustments. Perhaps this should be refined to check for any
991 -- component associations that actually need tag adjustment, similar
992 -- to the test in Component_OK_For_Backend for record aggregates with
993 -- tagged components, but not clear whether it's worthwhile ???; in the
994 -- case of virtual machines (no Tagged_Type_Expansion), object tags are
995 -- handled implicitly).
997 if Is_Tagged_Type
(Component_Type
(Typ
))
998 and then Tagged_Type_Expansion
1003 -- Checks 6 (component type must not have bit aligned components)
1005 if Type_May_Have_Bit_Aligned_Components
(Component_Type
(Typ
)) then
1009 -- Backend processing is possible
1012 end Backend_Processing_Possible
;
1014 ---------------------------
1015 -- Build_Array_Aggr_Code --
1016 ---------------------------
1018 -- The code that we generate from a one dimensional aggregate is
1020 -- 1. If the subaggregate contains discrete choices we
1022 -- (a) Sort the discrete choices
1024 -- (b) Otherwise for each discrete choice that specifies a range we
1025 -- emit a loop. If a range specifies a maximum of three values, or
1026 -- we are dealing with an expression we emit a sequence of
1027 -- assignments instead of a loop.
1029 -- (c) Generate the remaining loops to cover the others choice if any
1031 -- 2. If the aggregate contains positional elements we
1033 -- (a) Translate the positional elements in a series of assignments
1035 -- (b) Generate a final loop to cover the others choice if any.
1036 -- Note that this final loop has to be a while loop since the case
1038 -- L : Integer := Integer'Last;
1039 -- H : Integer := Integer'Last;
1040 -- A : array (L .. H) := (1, others =>0);
1042 -- cannot be handled by a for loop. Thus for the following
1044 -- array (L .. H) := (.. positional elements.., others => E);
1046 -- we always generate something like:
1048 -- J : Index_Type := Index_Of_Last_Positional_Element;
1050 -- J := Index_Base'Succ (J)
1054 function Build_Array_Aggr_Code
1059 Scalar_Comp
: Boolean;
1060 Indexes
: List_Id
:= No_List
) return List_Id
1062 Loc
: constant Source_Ptr
:= Sloc
(N
);
1063 Index_Base
: constant Entity_Id
:= Base_Type
(Etype
(Index
));
1064 Index_Base_L
: constant Node_Id
:= Type_Low_Bound
(Index_Base
);
1065 Index_Base_H
: constant Node_Id
:= Type_High_Bound
(Index_Base
);
1067 function Add
(Val
: Int
; To
: Node_Id
) return Node_Id
;
1068 -- Returns an expression where Val is added to expression To, unless
1069 -- To+Val is provably out of To's base type range. To must be an
1070 -- already analyzed expression.
1072 function Empty_Range
(L
, H
: Node_Id
) return Boolean;
1073 -- Returns True if the range defined by L .. H is certainly empty
1075 function Equal
(L
, H
: Node_Id
) return Boolean;
1076 -- Returns True if L = H for sure
1078 function Index_Base_Name
return Node_Id
;
1079 -- Returns a new reference to the index type name
1084 In_Loop
: Boolean := False) return List_Id
;
1085 -- Ind must be a side-effect-free expression. If the input aggregate N
1086 -- to Build_Loop contains no subaggregates, then this function returns
1087 -- the assignment statement:
1089 -- Into (Indexes, Ind) := Expr;
1091 -- Otherwise we call Build_Code recursively. Flag In_Loop should be set
1092 -- when the assignment appears within a generated loop.
1094 -- Ada 2005 (AI-287): In case of default initialized component, Expr
1095 -- is empty and we generate a call to the corresponding IP subprogram.
1097 function Gen_Loop
(L
, H
: Node_Id
; Expr
: Node_Id
) return List_Id
;
1098 -- Nodes L and H must be side-effect-free expressions. If the input
1099 -- aggregate N to Build_Loop contains no subaggregates, this routine
1100 -- returns the for loop statement:
1102 -- for J in Index_Base'(L) .. Index_Base'(H) loop
1103 -- Into (Indexes, J) := Expr;
1106 -- Otherwise we call Build_Code recursively. As an optimization if the
1107 -- loop covers 3 or fewer scalar elements we generate a sequence of
1109 -- If the component association that generates the loop comes from an
1110 -- Iterated_Component_Association, the loop parameter has the name of
1111 -- the corresponding parameter in the original construct.
1113 function Gen_While
(L
, H
: Node_Id
; Expr
: Node_Id
) return List_Id
;
1114 -- Nodes L and H must be side-effect-free expressions. If the input
1115 -- aggregate N to Build_Loop contains no subaggregates, this routine
1116 -- returns the while loop statement:
1118 -- J : Index_Base := L;
1120 -- J := Index_Base'Succ (J);
1121 -- Into (Indexes, J) := Expr;
1124 -- Otherwise we call Build_Code recursively
1126 function Get_Assoc_Expr
(Assoc
: Node_Id
) return Node_Id
;
1127 -- For an association with a box, use value given by aspect
1128 -- Default_Component_Value of array type if specified, else use
1129 -- value given by aspect Default_Value for component type itself
1130 -- if specified, else return Empty.
1132 function Local_Compile_Time_Known_Value
(E
: Node_Id
) return Boolean;
1133 function Local_Expr_Value
(E
: Node_Id
) return Uint
;
1134 -- These two Local routines are used to replace the corresponding ones
1135 -- in sem_eval because while processing the bounds of an aggregate with
1136 -- discrete choices whose index type is an enumeration, we build static
1137 -- expressions not recognized by Compile_Time_Known_Value as such since
1138 -- they have not yet been analyzed and resolved. All the expressions in
1139 -- question are things like Index_Base_Name'Val (Const) which we can
1140 -- easily recognize as being constant.
1146 function Add
(Val
: Int
; To
: Node_Id
) return Node_Id
is
1151 U_Val
: constant Uint
:= UI_From_Int
(Val
);
1154 -- Note: do not try to optimize the case of Val = 0, because
1155 -- we need to build a new node with the proper Sloc value anyway.
1157 -- First test if we can do constant folding
1159 if Local_Compile_Time_Known_Value
(To
) then
1160 U_To
:= Local_Expr_Value
(To
) + Val
;
1162 -- Determine if our constant is outside the range of the index.
1163 -- If so return an Empty node. This empty node will be caught
1164 -- by Empty_Range below.
1166 if Compile_Time_Known_Value
(Index_Base_L
)
1167 and then U_To
< Expr_Value
(Index_Base_L
)
1171 elsif Compile_Time_Known_Value
(Index_Base_H
)
1172 and then U_To
> Expr_Value
(Index_Base_H
)
1177 Expr_Pos
:= Make_Integer_Literal
(Loc
, U_To
);
1178 Set_Is_Static_Expression
(Expr_Pos
);
1180 if not Is_Enumeration_Type
(Index_Base
) then
1183 -- If we are dealing with enumeration return
1184 -- Index_Base'Val (Expr_Pos)
1188 Make_Attribute_Reference
1190 Prefix
=> Index_Base_Name
,
1191 Attribute_Name
=> Name_Val
,
1192 Expressions
=> New_List
(Expr_Pos
));
1198 -- If we are here no constant folding possible
1200 if not Is_Enumeration_Type
(Index_Base
) then
1203 Left_Opnd
=> Duplicate_Subexpr
(To
),
1204 Right_Opnd
=> Make_Integer_Literal
(Loc
, U_Val
));
1206 -- If we are dealing with enumeration return
1207 -- Index_Base'Val (Index_Base'Pos (To) + Val)
1211 Make_Attribute_Reference
1213 Prefix
=> Index_Base_Name
,
1214 Attribute_Name
=> Name_Pos
,
1215 Expressions
=> New_List
(Duplicate_Subexpr
(To
)));
1219 Left_Opnd
=> To_Pos
,
1220 Right_Opnd
=> Make_Integer_Literal
(Loc
, U_Val
));
1223 Make_Attribute_Reference
1225 Prefix
=> Index_Base_Name
,
1226 Attribute_Name
=> Name_Val
,
1227 Expressions
=> New_List
(Expr_Pos
));
1237 function Empty_Range
(L
, H
: Node_Id
) return Boolean is
1238 Is_Empty
: Boolean := False;
1243 -- First check if L or H were already detected as overflowing the
1244 -- index base range type by function Add above. If this is so Add
1245 -- returns the empty node.
1247 if No
(L
) or else No
(H
) then
1251 for J
in 1 .. 3 loop
1254 -- L > H range is empty
1260 -- B_L > H range must be empty
1263 Low
:= Index_Base_L
;
1266 -- L > B_H range must be empty
1270 High
:= Index_Base_H
;
1273 if Local_Compile_Time_Known_Value
(Low
)
1275 Local_Compile_Time_Known_Value
(High
)
1278 UI_Gt
(Local_Expr_Value
(Low
), Local_Expr_Value
(High
));
1291 function Equal
(L
, H
: Node_Id
) return Boolean is
1296 elsif Local_Compile_Time_Known_Value
(L
)
1298 Local_Compile_Time_Known_Value
(H
)
1300 return UI_Eq
(Local_Expr_Value
(L
), Local_Expr_Value
(H
));
1313 In_Loop
: Boolean := False) return List_Id
1315 function Add_Loop_Actions
(Lis
: List_Id
) return List_Id
;
1316 -- Collect insert_actions generated in the construction of a loop,
1317 -- and prepend them to the sequence of assignments to complete the
1318 -- eventual body of the loop.
1320 procedure Initialize_Array_Component
1321 (Arr_Comp
: Node_Id
;
1323 Init_Expr
: Node_Id
;
1325 -- Perform the initialization of array component Arr_Comp with
1326 -- expected type Comp_Typ. Init_Expr denotes the initialization
1327 -- expression of the array component. All generated code is added
1330 procedure Initialize_Ctrl_Array_Component
1331 (Arr_Comp
: Node_Id
;
1332 Comp_Typ
: Entity_Id
;
1333 Init_Expr
: Node_Id
;
1335 -- Perform the initialization of array component Arr_Comp when its
1336 -- expected type Comp_Typ needs finalization actions. Init_Expr is
1337 -- the initialization expression of the array component. All hook-
1338 -- related declarations are inserted prior to aggregate N. Remaining
1339 -- code is added to list Stmts.
1341 ----------------------
1342 -- Add_Loop_Actions --
1343 ----------------------
1345 function Add_Loop_Actions
(Lis
: List_Id
) return List_Id
is
1349 -- Ada 2005 (AI-287): Do nothing else in case of default
1350 -- initialized component.
1355 elsif Nkind
(Parent
(Expr
)) = N_Component_Association
1356 and then Present
(Loop_Actions
(Parent
(Expr
)))
1358 Append_List
(Lis
, Loop_Actions
(Parent
(Expr
)));
1359 Res
:= Loop_Actions
(Parent
(Expr
));
1360 Set_Loop_Actions
(Parent
(Expr
), No_List
);
1366 end Add_Loop_Actions
;
1368 --------------------------------
1369 -- Initialize_Array_Component --
1370 --------------------------------
1372 procedure Initialize_Array_Component
1373 (Arr_Comp
: Node_Id
;
1375 Init_Expr
: Node_Id
;
1378 Exceptions_OK
: constant Boolean :=
1379 not Restriction_Active
1380 (No_Exception_Propagation
);
1382 Finalization_OK
: constant Boolean :=
1384 and then Needs_Finalization
(Comp_Typ
);
1386 Full_Typ
: constant Entity_Id
:= Underlying_Type
(Comp_Typ
);
1388 Blk_Stmts
: List_Id
;
1389 Init_Stmt
: Node_Id
;
1392 -- Protect the initialization statements from aborts. Generate:
1396 if Finalization_OK
and Abort_Allowed
then
1397 if Exceptions_OK
then
1398 Blk_Stmts
:= New_List
;
1403 Append_To
(Blk_Stmts
, Build_Runtime_Call
(Loc
, RE_Abort_Defer
));
1405 -- Otherwise aborts are not allowed. All generated code is added
1406 -- directly to the input list.
1412 -- Initialize the array element. Generate:
1414 -- Arr_Comp := Init_Expr;
1416 -- Note that the initialization expression is replicated because
1417 -- it has to be reevaluated within a generated loop.
1420 Make_OK_Assignment_Statement
(Loc
,
1421 Name
=> New_Copy_Tree
(Arr_Comp
),
1422 Expression
=> New_Copy_Tree
(Init_Expr
));
1423 Set_No_Ctrl_Actions
(Init_Stmt
);
1425 -- If this is an aggregate for an array of arrays, each
1426 -- subaggregate will be expanded as well, and even with
1427 -- No_Ctrl_Actions the assignments of inner components will
1428 -- require attachment in their assignments to temporaries. These
1429 -- temporaries must be finalized for each subaggregate. Generate:
1432 -- Arr_Comp := Init_Expr;
1435 if Finalization_OK
and then Is_Array_Type
(Comp_Typ
) then
1437 Make_Block_Statement
(Loc
,
1438 Handled_Statement_Sequence
=>
1439 Make_Handled_Sequence_Of_Statements
(Loc
,
1440 Statements
=> New_List
(Init_Stmt
)));
1443 Append_To
(Blk_Stmts
, Init_Stmt
);
1445 -- Adjust the tag due to a possible view conversion. Generate:
1447 -- Arr_Comp._tag := Full_TypP;
1449 if Tagged_Type_Expansion
1450 and then Present
(Comp_Typ
)
1451 and then Is_Tagged_Type
(Comp_Typ
)
1453 Append_To
(Blk_Stmts
,
1454 Make_OK_Assignment_Statement
(Loc
,
1456 Make_Selected_Component
(Loc
,
1457 Prefix
=> New_Copy_Tree
(Arr_Comp
),
1460 (First_Tag_Component
(Full_Typ
), Loc
)),
1463 Unchecked_Convert_To
(RTE
(RE_Tag
),
1465 (Node
(First_Elmt
(Access_Disp_Table
(Full_Typ
))),
1469 -- Adjust the array component. Controlled subaggregates are not
1470 -- considered because each of their individual elements will
1471 -- receive an adjustment of its own. Generate:
1473 -- [Deep_]Adjust (Arr_Comp);
1476 and then not Is_Limited_Type
(Comp_Typ
)
1477 and then not Is_Build_In_Place_Function_Call
(Init_Expr
)
1479 (Is_Array_Type
(Comp_Typ
)
1480 and then Is_Controlled
(Component_Type
(Comp_Typ
))
1481 and then Nkind
(Expr
) = N_Aggregate
)
1485 (Obj_Ref
=> New_Copy_Tree
(Arr_Comp
),
1488 -- Guard against a missing [Deep_]Adjust when the component
1489 -- type was not frozen properly.
1491 if Present
(Adj_Call
) then
1492 Append_To
(Blk_Stmts
, Adj_Call
);
1496 -- Complete the protection of the initialization statements
1498 if Finalization_OK
and Abort_Allowed
then
1500 -- Wrap the initialization statements in a block to catch a
1501 -- potential exception. Generate:
1505 -- Arr_Comp := Init_Expr;
1506 -- Arr_Comp._tag := Full_TypP;
1507 -- [Deep_]Adjust (Arr_Comp);
1509 -- Abort_Undefer_Direct;
1512 if Exceptions_OK
then
1514 Build_Abort_Undefer_Block
(Loc
,
1518 -- Otherwise exceptions are not propagated. Generate:
1521 -- Arr_Comp := Init_Expr;
1522 -- Arr_Comp._tag := Full_TypP;
1523 -- [Deep_]Adjust (Arr_Comp);
1527 Append_To
(Blk_Stmts
,
1528 Build_Runtime_Call
(Loc
, RE_Abort_Undefer
));
1531 end Initialize_Array_Component
;
1533 -------------------------------------
1534 -- Initialize_Ctrl_Array_Component --
1535 -------------------------------------
1537 procedure Initialize_Ctrl_Array_Component
1538 (Arr_Comp
: Node_Id
;
1539 Comp_Typ
: Entity_Id
;
1540 Init_Expr
: Node_Id
;
1544 Act_Stmts
: List_Id
;
1547 Hook_Clear
: Node_Id
;
1549 In_Place_Expansion
: Boolean;
1550 -- Flag set when a nonlimited controlled function call requires
1551 -- in-place expansion.
1554 -- Duplicate the initialization expression in case the context is
1555 -- a multi choice list or an "others" choice which plugs various
1556 -- holes in the aggregate. As a result the expression is no longer
1557 -- shared between the various components and is reevaluated for
1558 -- each such component.
1560 Expr
:= New_Copy_Tree
(Init_Expr
);
1561 Set_Parent
(Expr
, Parent
(Init_Expr
));
1563 -- Perform a preliminary analysis and resolution to determine what
1564 -- the initialization expression denotes. An unanalyzed function
1565 -- call may appear as an identifier or an indexed component.
1567 if Nkind
(Expr
) in N_Function_Call
1569 | N_Indexed_Component
1570 and then not Analyzed
(Expr
)
1572 Preanalyze_And_Resolve
(Expr
, Comp_Typ
);
1575 In_Place_Expansion
:=
1576 Nkind
(Expr
) = N_Function_Call
1577 and then not Is_Build_In_Place_Result_Type
(Comp_Typ
);
1579 -- The initialization expression is a controlled function call.
1580 -- Perform in-place removal of side effects to avoid creating a
1581 -- transient scope, which leads to premature finalization.
1583 -- This in-place expansion is not performed for limited transient
1584 -- objects, because the initialization is already done in place.
1586 if In_Place_Expansion
then
1588 -- Suppress the removal of side effects by general analysis,
1589 -- because this behavior is emulated here. This avoids the
1590 -- generation of a transient scope, which leads to out-of-order
1591 -- adjustment and finalization.
1593 Set_No_Side_Effect_Removal
(Expr
);
1595 -- When the transient component initialization is related to a
1596 -- range or an "others", keep all generated statements within
1597 -- the enclosing loop. This way the controlled function call
1598 -- will be evaluated at each iteration, and its result will be
1599 -- finalized at the end of each iteration.
1605 -- Otherwise this is a single component initialization. Hook-
1606 -- related statements are inserted prior to the aggregate.
1610 Act_Stmts
:= No_List
;
1613 -- Install all hook-related declarations and prepare the clean
1616 Process_Transient_Component
1618 Comp_Typ
=> Comp_Typ
,
1620 Fin_Call
=> Fin_Call
,
1621 Hook_Clear
=> Hook_Clear
,
1623 Stmts
=> Act_Stmts
);
1626 -- Use the noncontrolled component initialization circuitry to
1627 -- assign the result of the function call to the array element.
1628 -- This also performs subaggregate wrapping, tag adjustment, and
1629 -- [deep] adjustment of the array element.
1631 Initialize_Array_Component
1632 (Arr_Comp
=> Arr_Comp
,
1633 Comp_Typ
=> Comp_Typ
,
1637 -- At this point the array element is fully initialized. Complete
1638 -- the processing of the controlled array component by finalizing
1639 -- the transient function result.
1641 if In_Place_Expansion
then
1642 Process_Transient_Component_Completion
1645 Fin_Call
=> Fin_Call
,
1646 Hook_Clear
=> Hook_Clear
,
1649 end Initialize_Ctrl_Array_Component
;
1653 Stmts
: constant List_Id
:= New_List
;
1655 Comp_Typ
: Entity_Id
:= Empty
;
1657 Indexed_Comp
: Node_Id
;
1658 Init_Call
: Node_Id
;
1659 New_Indexes
: List_Id
;
1661 -- Start of processing for Gen_Assign
1664 if No
(Indexes
) then
1665 New_Indexes
:= New_List
;
1667 New_Indexes
:= New_Copy_List_Tree
(Indexes
);
1670 Append_To
(New_Indexes
, Ind
);
1672 if Present
(Next_Index
(Index
)) then
1675 Build_Array_Aggr_Code
1678 Index
=> Next_Index
(Index
),
1680 Scalar_Comp
=> Scalar_Comp
,
1681 Indexes
=> New_Indexes
));
1684 -- If we get here then we are at a bottom-level (sub-)aggregate
1688 (Make_Indexed_Component
(Loc
,
1689 Prefix
=> New_Copy_Tree
(Into
),
1690 Expressions
=> New_Indexes
));
1692 Set_Assignment_OK
(Indexed_Comp
);
1694 -- Ada 2005 (AI-287): In case of default initialized component, Expr
1695 -- is not present (and therefore we also initialize Expr_Q to empty).
1699 elsif Nkind
(Expr
) = N_Qualified_Expression
then
1700 Expr_Q
:= Expression
(Expr
);
1705 if Present
(Etype
(N
)) and then Etype
(N
) /= Any_Composite
then
1706 Comp_Typ
:= Component_Type
(Etype
(N
));
1707 pragma Assert
(Comp_Typ
= Ctype
); -- AI-287
1709 elsif Present
(Next
(First
(New_Indexes
))) then
1711 -- Ada 2005 (AI-287): Do nothing in case of default initialized
1712 -- component because we have received the component type in
1713 -- the formal parameter Ctype.
1715 -- ??? Some assert pragmas have been added to check if this new
1716 -- formal can be used to replace this code in all cases.
1718 if Present
(Expr
) then
1720 -- This is a multidimensional array. Recover the component type
1721 -- from the outermost aggregate, because subaggregates do not
1722 -- have an assigned type.
1729 while Present
(P
) loop
1730 if Nkind
(P
) = N_Aggregate
1731 and then Present
(Etype
(P
))
1733 Comp_Typ
:= Component_Type
(Etype
(P
));
1741 pragma Assert
(Comp_Typ
= Ctype
); -- AI-287
1746 -- Ada 2005 (AI-287): We only analyze the expression in case of non-
1747 -- default initialized components (otherwise Expr_Q is not present).
1750 and then Nkind
(Expr_Q
) in N_Aggregate | N_Extension_Aggregate
1752 -- At this stage the Expression may not have been analyzed yet
1753 -- because the array aggregate code has not been updated to use
1754 -- the Expansion_Delayed flag and avoid analysis altogether to
1755 -- solve the same problem (see Resolve_Aggr_Expr). So let us do
1756 -- the analysis of non-array aggregates now in order to get the
1757 -- value of Expansion_Delayed flag for the inner aggregate ???
1759 -- In the case of an iterated component association, the analysis
1760 -- of the generated loop will analyze the expression in the
1761 -- proper context, in which the loop parameter is visible.
1763 if Present
(Comp_Typ
) and then not Is_Array_Type
(Comp_Typ
) then
1764 if Nkind
(Parent
(Expr_Q
)) = N_Iterated_Component_Association
1765 or else Nkind
(Parent
(Parent
((Expr_Q
)))) =
1766 N_Iterated_Component_Association
1770 Analyze_And_Resolve
(Expr_Q
, Comp_Typ
);
1774 if Is_Delayed_Aggregate
(Expr_Q
) then
1776 -- This is either a subaggregate of a multidimensional array,
1777 -- or a component of an array type whose component type is
1778 -- also an array. In the latter case, the expression may have
1779 -- component associations that provide different bounds from
1780 -- those of the component type, and sliding must occur. Instead
1781 -- of decomposing the current aggregate assignment, force the
1782 -- reanalysis of the assignment, so that a temporary will be
1783 -- generated in the usual fashion, and sliding will take place.
1785 if Nkind
(Parent
(N
)) = N_Assignment_Statement
1786 and then Is_Array_Type
(Comp_Typ
)
1787 and then Present
(Component_Associations
(Expr_Q
))
1788 and then Must_Slide
(N
, Comp_Typ
, Etype
(Expr_Q
))
1790 Set_Expansion_Delayed
(Expr_Q
, False);
1791 Set_Analyzed
(Expr_Q
, False);
1796 Late_Expansion
(Expr_Q
, Etype
(Expr_Q
), Indexed_Comp
));
1801 if Present
(Expr
) then
1803 -- Handle an initialization expression of a controlled type in
1804 -- case it denotes a function call. In general such a scenario
1805 -- will produce a transient scope, but this will lead to wrong
1806 -- order of initialization, adjustment, and finalization in the
1807 -- context of aggregates.
1809 -- Target (1) := Ctrl_Func_Call;
1812 -- Trans_Obj : ... := Ctrl_Func_Call; -- object
1813 -- Target (1) := Trans_Obj;
1814 -- Finalize (Trans_Obj);
1816 -- Target (1)._tag := ...;
1817 -- Adjust (Target (1));
1819 -- In the example above, the call to Finalize occurs too early
1820 -- and as a result it may leave the array component in a bad
1821 -- state. Finalization of the transient object should really
1822 -- happen after adjustment.
1824 -- To avoid this scenario, perform in-place side-effect removal
1825 -- of the function call. This eliminates the transient property
1826 -- of the function result and ensures correct order of actions.
1828 -- Res : ... := Ctrl_Func_Call;
1829 -- Target (1) := Res;
1830 -- Target (1)._tag := ...;
1831 -- Adjust (Target (1));
1834 if Present
(Comp_Typ
)
1835 and then Needs_Finalization
(Comp_Typ
)
1836 and then Nkind
(Expr
) /= N_Aggregate
1838 Initialize_Ctrl_Array_Component
1839 (Arr_Comp
=> Indexed_Comp
,
1840 Comp_Typ
=> Comp_Typ
,
1844 -- Otherwise perform simple component initialization
1847 Initialize_Array_Component
1848 (Arr_Comp
=> Indexed_Comp
,
1849 Comp_Typ
=> Comp_Typ
,
1854 -- Ada 2005 (AI-287): In case of default initialized component, call
1855 -- the initialization subprogram associated with the component type.
1856 -- If the component type is an access type, add an explicit null
1857 -- assignment, because for the back-end there is an initialization
1858 -- present for the whole aggregate, and no default initialization
1861 -- In addition, if the component type is controlled, we must call
1862 -- its Initialize procedure explicitly, because there is no explicit
1863 -- object creation that will invoke it otherwise.
1866 if Present
(Base_Init_Proc
(Base_Type
(Ctype
)))
1867 or else Has_Task
(Base_Type
(Ctype
))
1869 Append_List_To
(Stmts
,
1870 Build_Initialization_Call
(Loc
,
1871 Id_Ref
=> Indexed_Comp
,
1873 With_Default_Init
=> True));
1875 -- If the component type has invariants, add an invariant
1876 -- check after the component is default-initialized. It will
1877 -- be analyzed and resolved before the code for initialization
1878 -- of other components.
1880 if Has_Invariants
(Ctype
) then
1881 Set_Etype
(Indexed_Comp
, Ctype
);
1882 Append_To
(Stmts
, Make_Invariant_Call
(Indexed_Comp
));
1886 if Needs_Finalization
(Ctype
) then
1889 (Obj_Ref
=> New_Copy_Tree
(Indexed_Comp
),
1892 -- Guard against a missing [Deep_]Initialize when the component
1893 -- type was not properly frozen.
1895 if Present
(Init_Call
) then
1896 Append_To
(Stmts
, Init_Call
);
1900 -- If Default_Initial_Condition applies to the component type,
1901 -- add a DIC check after the component is default-initialized,
1902 -- as well as after an Initialize procedure is called, in the
1903 -- case of components of a controlled type. It will be analyzed
1904 -- and resolved before the code for initialization of other
1907 -- Theoretically this might also be needed for cases where Expr
1908 -- is not empty, but a default init still applies, such as for
1909 -- Default_Value cases, in which case we won't get here. ???
1911 if Has_DIC
(Ctype
) and then Present
(DIC_Procedure
(Ctype
)) then
1913 Build_DIC_Call
(Loc
, New_Copy_Tree
(Indexed_Comp
), Ctype
));
1917 return Add_Loop_Actions
(Stmts
);
1924 function Gen_Loop
(L
, H
: Node_Id
; Expr
: Node_Id
) return List_Id
is
1925 Is_Iterated_Component
: constant Boolean :=
1926 Parent_Kind
(Expr
) = N_Iterated_Component_Association
;
1939 -- Index_Base'(L) .. Index_Base'(H)
1941 L_Iteration_Scheme
: Node_Id
;
1942 -- L_J in Index_Base'(L) .. Index_Base'(H)
1945 -- The statements to execute in the loop
1947 S
: constant List_Id
:= New_List
;
1948 -- List of statements
1951 -- Copy of expression tree, used for checking purposes
1954 -- If loop bounds define an empty range return the null statement
1956 if Empty_Range
(L
, H
) then
1957 Append_To
(S
, Make_Null_Statement
(Loc
));
1959 -- Ada 2005 (AI-287): Nothing else need to be done in case of
1960 -- default initialized component.
1966 -- The expression must be type-checked even though no component
1967 -- of the aggregate will have this value. This is done only for
1968 -- actual components of the array, not for subaggregates. Do
1969 -- the check on a copy, because the expression may be shared
1970 -- among several choices, some of which might be non-null.
1972 if Present
(Etype
(N
))
1973 and then Is_Array_Type
(Etype
(N
))
1974 and then No
(Next_Index
(Index
))
1976 Expander_Mode_Save_And_Set
(False);
1977 Tcopy
:= New_Copy_Tree
(Expr
);
1978 Set_Parent
(Tcopy
, N
);
1980 -- For iterated_component_association analyze and resolve
1981 -- the expression with name of the index parameter visible.
1982 -- To manipulate scopes, we use entity of the implicit loop.
1984 if Is_Iterated_Component
then
1986 Index_Parameter
: constant Entity_Id
:=
1987 Defining_Identifier
(Parent
(Expr
));
1989 Push_Scope
(Scope
(Index_Parameter
));
1990 Enter_Name
(Index_Parameter
);
1992 (Tcopy
, Component_Type
(Etype
(N
)));
1996 -- For ordinary component association, just analyze and
1997 -- resolve the expression.
2000 Analyze_And_Resolve
(Tcopy
, Component_Type
(Etype
(N
)));
2003 Expander_Mode_Restore
;
2009 -- If loop bounds are the same then generate an assignment, unless
2010 -- the parent construct is an Iterated_Component_Association.
2012 elsif Equal
(L
, H
) and then not Is_Iterated_Component
then
2013 return Gen_Assign
(New_Copy_Tree
(L
), Expr
);
2015 -- If H - L <= 2 then generate a sequence of assignments when we are
2016 -- processing the bottom most aggregate and it contains scalar
2019 elsif No
(Next_Index
(Index
))
2020 and then Scalar_Comp
2021 and then Local_Compile_Time_Known_Value
(L
)
2022 and then Local_Compile_Time_Known_Value
(H
)
2023 and then Local_Expr_Value
(H
) - Local_Expr_Value
(L
) <= 2
2024 and then not Is_Iterated_Component
2026 Append_List_To
(S
, Gen_Assign
(New_Copy_Tree
(L
), Expr
));
2027 Append_List_To
(S
, Gen_Assign
(Add
(1, To
=> L
), Expr
));
2029 if Local_Expr_Value
(H
) - Local_Expr_Value
(L
) = 2 then
2030 Append_List_To
(S
, Gen_Assign
(Add
(2, To
=> L
), Expr
));
2036 -- Otherwise construct the loop, starting with the loop index L_J
2038 if Is_Iterated_Component
then
2040 -- Create a new scope for the loop variable so that the
2041 -- following Gen_Assign (that ends up calling
2042 -- Preanalyze_And_Resolve) can correctly find it.
2044 Ent
:= New_Internal_Entity
(E_Loop
,
2045 Current_Scope
, Loc
, 'L');
2046 Set_Etype
(Ent
, Standard_Void_Type
);
2047 Set_Parent
(Ent
, Parent
(Parent
(Expr
)));
2051 Make_Defining_Identifier
(Loc
,
2052 Chars
=> (Chars
(Defining_Identifier
(Parent
(Expr
)))));
2056 -- The Etype will be set by a later Analyze call.
2057 Set_Etype
(L_J
, Any_Type
);
2059 Mutate_Ekind
(L_J
, E_Variable
);
2060 Set_Is_Not_Self_Hidden
(L_J
);
2061 Set_Scope
(L_J
, Ent
);
2063 L_J
:= Make_Temporary
(Loc
, 'J', L
);
2066 -- Construct "L .. H" in Index_Base. We use a qualified expression
2067 -- for the bound to convert to the index base, but we don't need
2068 -- to do that if we already have the base type at hand.
2070 if Etype
(L
) = Index_Base
then
2071 L_L
:= New_Copy_Tree
(L
);
2074 Make_Qualified_Expression
(Loc
,
2075 Subtype_Mark
=> Index_Base_Name
,
2076 Expression
=> New_Copy_Tree
(L
));
2079 if Etype
(H
) = Index_Base
then
2080 L_H
:= New_Copy_Tree
(H
);
2083 Make_Qualified_Expression
(Loc
,
2084 Subtype_Mark
=> Index_Base_Name
,
2085 Expression
=> New_Copy_Tree
(H
));
2093 -- Construct "for L_J in Index_Base range L .. H"
2095 L_Iteration_Scheme
:=
2096 Make_Iteration_Scheme
(Loc
,
2097 Loop_Parameter_Specification
=>
2098 Make_Loop_Parameter_Specification
(Loc
,
2099 Defining_Identifier
=> L_J
,
2100 Discrete_Subtype_Definition
=> L_Range
));
2102 -- Construct the statements to execute in the loop body
2105 Gen_Assign
(New_Occurrence_Of
(L_J
, Loc
), Expr
, In_Loop
=> True);
2107 -- Construct the final loop
2110 Make_Implicit_Loop_Statement
2112 Identifier
=> Empty
,
2113 Iteration_Scheme
=> L_Iteration_Scheme
,
2114 Statements
=> L_Body
));
2116 if Is_Iterated_Component
then
2120 -- A small optimization: if the aggregate is initialized with a box
2121 -- and the component type has no initialization procedure, remove the
2122 -- useless empty loop.
2124 if Nkind
(First
(S
)) = N_Loop_Statement
2125 and then Is_Empty_List
(Statements
(First
(S
)))
2127 return New_List
(Make_Null_Statement
(Loc
));
2137 -- The code built is
2139 -- W_J : Index_Base := L;
2140 -- while W_J < H loop
2141 -- W_J := Index_Base'Succ (W);
2145 function Gen_While
(L
, H
: Node_Id
; Expr
: Node_Id
) return List_Id
is
2149 -- W_J : Base_Type := L;
2151 W_Iteration_Scheme
: Node_Id
;
2154 W_Index_Succ
: Node_Id
;
2155 -- Index_Base'Succ (J)
2157 W_Increment
: Node_Id
;
2158 -- W_J := Index_Base'Succ (W)
2160 W_Body
: constant List_Id
:= New_List
;
2161 -- The statements to execute in the loop
2163 S
: constant List_Id
:= New_List
;
2164 -- list of statement
2167 -- If loop bounds define an empty range or are equal return null
2169 if Empty_Range
(L
, H
) or else Equal
(L
, H
) then
2170 Append_To
(S
, Make_Null_Statement
(Loc
));
2174 -- Build the decl of W_J
2176 W_J
:= Make_Temporary
(Loc
, 'J', L
);
2178 Make_Object_Declaration
2180 Defining_Identifier
=> W_J
,
2181 Object_Definition
=> Index_Base_Name
,
2184 -- Theoretically we should do a New_Copy_Tree (L) here, but we know
2185 -- that in this particular case L is a fresh Expr generated by
2186 -- Add which we are the only ones to use.
2188 Append_To
(S
, W_Decl
);
2190 -- Construct " while W_J < H"
2192 W_Iteration_Scheme
:=
2193 Make_Iteration_Scheme
2195 Condition
=> Make_Op_Lt
2197 Left_Opnd
=> New_Occurrence_Of
(W_J
, Loc
),
2198 Right_Opnd
=> New_Copy_Tree
(H
)));
2200 -- Construct the statements to execute in the loop body
2203 Make_Attribute_Reference
2205 Prefix
=> Index_Base_Name
,
2206 Attribute_Name
=> Name_Succ
,
2207 Expressions
=> New_List
(New_Occurrence_Of
(W_J
, Loc
)));
2210 Make_OK_Assignment_Statement
2212 Name
=> New_Occurrence_Of
(W_J
, Loc
),
2213 Expression
=> W_Index_Succ
);
2215 Append_To
(W_Body
, W_Increment
);
2217 Append_List_To
(W_Body
,
2218 Gen_Assign
(New_Occurrence_Of
(W_J
, Loc
), Expr
, In_Loop
=> True));
2220 -- Construct the final loop
2223 Make_Implicit_Loop_Statement
2225 Identifier
=> Empty
,
2226 Iteration_Scheme
=> W_Iteration_Scheme
,
2227 Statements
=> W_Body
));
2232 --------------------
2233 -- Get_Assoc_Expr --
2234 --------------------
2236 function Get_Assoc_Expr
(Assoc
: Node_Id
) return Node_Id
is
2237 Typ
: constant Entity_Id
:= Base_Type
(Etype
(N
));
2240 if Box_Present
(Assoc
) then
2241 if Present
(Default_Aspect_Component_Value
(Typ
)) then
2242 return Default_Aspect_Component_Value
(Typ
);
2243 elsif Needs_Simple_Initialization
(Ctype
) then
2244 return Get_Simple_Init_Val
(Ctype
, N
);
2250 return Expression
(Assoc
);
2254 ---------------------
2255 -- Index_Base_Name --
2256 ---------------------
2258 function Index_Base_Name
return Node_Id
is
2260 return New_Occurrence_Of
(Index_Base
, Sloc
(N
));
2261 end Index_Base_Name
;
2263 ------------------------------------
2264 -- Local_Compile_Time_Known_Value --
2265 ------------------------------------
2267 function Local_Compile_Time_Known_Value
(E
: Node_Id
) return Boolean is
2269 return Compile_Time_Known_Value
(E
)
2271 (Nkind
(E
) = N_Attribute_Reference
2272 and then Attribute_Name
(E
) = Name_Val
2273 and then Compile_Time_Known_Value
(First
(Expressions
(E
))));
2274 end Local_Compile_Time_Known_Value
;
2276 ----------------------
2277 -- Local_Expr_Value --
2278 ----------------------
2280 function Local_Expr_Value
(E
: Node_Id
) return Uint
is
2282 if Compile_Time_Known_Value
(E
) then
2283 return Expr_Value
(E
);
2285 return Expr_Value
(First
(Expressions
(E
)));
2287 end Local_Expr_Value
;
2291 New_Code
: constant List_Id
:= New_List
;
2293 Aggr_Bounds
: constant Range_Nodes
:=
2294 Get_Index_Bounds
(Aggregate_Bounds
(N
));
2295 Aggr_L
: Node_Id
renames Aggr_Bounds
.First
;
2296 Aggr_H
: Node_Id
renames Aggr_Bounds
.Last
;
2297 -- The aggregate bounds of this specific subaggregate. Note that if the
2298 -- code generated by Build_Array_Aggr_Code is executed then these bounds
2299 -- are OK. Otherwise a Constraint_Error would have been raised.
2301 Aggr_Low
: constant Node_Id
:= Duplicate_Subexpr_No_Checks
(Aggr_L
);
2302 Aggr_High
: constant Node_Id
:= Duplicate_Subexpr_No_Checks
(Aggr_H
);
2303 -- After Duplicate_Subexpr these are side-effect free
2310 Bounds
: Range_Nodes
;
2311 Low
: Node_Id
renames Bounds
.First
;
2312 High
: Node_Id
renames Bounds
.Last
;
2314 Nb_Choices
: Nat
:= 0;
2315 Table
: Case_Table_Type
(1 .. Number_Of_Choices
(N
));
2316 -- Used to sort all the different choice values
2319 -- Number of elements in the positional aggregate
2321 Others_Assoc
: Node_Id
:= Empty
;
2323 -- Start of processing for Build_Array_Aggr_Code
2326 -- First before we start, a special case. if we have a bit packed
2327 -- array represented as a modular type, then clear the value to
2328 -- zero first, to ensure that unused bits are properly cleared.
2333 and then Is_Bit_Packed_Array
(Typ
)
2334 and then Is_Modular_Integer_Type
(Packed_Array_Impl_Type
(Typ
))
2337 Zero
: constant Node_Id
:= Make_Integer_Literal
(Loc
, Uint_0
);
2339 Analyze_And_Resolve
(Zero
, Packed_Array_Impl_Type
(Typ
));
2340 Append_To
(New_Code
,
2341 Make_Assignment_Statement
(Loc
,
2342 Name
=> New_Copy_Tree
(Into
),
2343 Expression
=> Unchecked_Convert_To
(Typ
, Zero
)));
2347 -- If the component type contains tasks, we need to build a Master
2348 -- entity in the current scope, because it will be needed if build-
2349 -- in-place functions are called in the expanded code.
2351 if Nkind
(Parent
(N
)) = N_Object_Declaration
and then Has_Task
(Typ
) then
2352 Build_Master_Entity
(Defining_Identifier
(Parent
(N
)));
2355 -- STEP 1: Process component associations
2357 -- For those associations that may generate a loop, initialize
2358 -- Loop_Actions to collect inserted actions that may be crated.
2360 -- Skip this if no component associations
2362 if No
(Expressions
(N
)) then
2364 -- STEP 1 (a): Sort the discrete choices
2366 Assoc
:= First
(Component_Associations
(N
));
2367 while Present
(Assoc
) loop
2368 Choice
:= First
(Choice_List
(Assoc
));
2369 while Present
(Choice
) loop
2370 if Nkind
(Choice
) = N_Others_Choice
then
2371 Others_Assoc
:= Assoc
;
2375 Bounds
:= Get_Index_Bounds
(Choice
);
2378 Set_Loop_Actions
(Assoc
, New_List
);
2381 Nb_Choices
:= Nb_Choices
+ 1;
2383 Table
(Nb_Choices
) :=
2386 Choice_Node
=> Get_Assoc_Expr
(Assoc
));
2394 -- If there is more than one set of choices these must be static
2395 -- and we can therefore sort them. Remember that Nb_Choices does not
2396 -- account for an others choice.
2398 if Nb_Choices
> 1 then
2399 Sort_Case_Table
(Table
);
2402 -- STEP 1 (b): take care of the whole set of discrete choices
2404 for J
in 1 .. Nb_Choices
loop
2405 Low
:= Table
(J
).Choice_Lo
;
2406 High
:= Table
(J
).Choice_Hi
;
2407 Expr
:= Table
(J
).Choice_Node
;
2408 Append_List
(Gen_Loop
(Low
, High
, Expr
), To
=> New_Code
);
2411 -- STEP 1 (c): generate the remaining loops to cover others choice
2412 -- We don't need to generate loops over empty gaps, but if there is
2413 -- a single empty range we must analyze the expression for semantics
2415 if Present
(Others_Assoc
) then
2417 First
: Boolean := True;
2421 for J
in 0 .. Nb_Choices
loop
2425 Low
:= Add
(1, To
=> Table
(J
).Choice_Hi
);
2428 if J
= Nb_Choices
then
2431 High
:= Add
(-1, To
=> Table
(J
+ 1).Choice_Lo
);
2434 -- If this is an expansion within an init proc, make
2435 -- sure that discriminant references are replaced by
2436 -- the corresponding discriminal.
2438 if Inside_Init_Proc
then
2439 if Is_Entity_Name
(Low
)
2440 and then Ekind
(Entity
(Low
)) = E_Discriminant
2442 Set_Entity
(Low
, Discriminal
(Entity
(Low
)));
2445 if Is_Entity_Name
(High
)
2446 and then Ekind
(Entity
(High
)) = E_Discriminant
2448 Set_Entity
(High
, Discriminal
(Entity
(High
)));
2453 or else not Empty_Range
(Low
, High
)
2457 -- Duplicate the expression in case we will be generating
2458 -- several loops. As a result the expression is no longer
2459 -- shared between the loops and is reevaluated for each
2462 Expr
:= Get_Assoc_Expr
(Others_Assoc
);
2463 Dup_Expr
:= New_Copy_Tree
(Expr
);
2464 Copy_Parent
(To
=> Dup_Expr
, From
=> Expr
);
2466 Set_Loop_Actions
(Others_Assoc
, New_List
);
2468 (Gen_Loop
(Low
, High
, Dup_Expr
), To
=> New_Code
);
2474 -- STEP 2: Process positional components
2477 -- STEP 2 (a): Generate the assignments for each positional element
2478 -- Note that here we have to use Aggr_L rather than Aggr_Low because
2479 -- Aggr_L is analyzed and Add wants an analyzed expression.
2481 Expr
:= First
(Expressions
(N
));
2483 while Present
(Expr
) loop
2484 Nb_Elements
:= Nb_Elements
+ 1;
2485 Append_List
(Gen_Assign
(Add
(Nb_Elements
, To
=> Aggr_L
), Expr
),
2490 -- STEP 2 (b): Generate final loop if an others choice is present.
2491 -- Here Nb_Elements gives the offset of the last positional element.
2493 if Present
(Component_Associations
(N
)) then
2494 Assoc
:= Last
(Component_Associations
(N
));
2496 if Nkind
(Assoc
) = N_Iterated_Component_Association
then
2497 -- Ada 2022: generate a loop to have a proper scope for
2498 -- the identifier that typically appears in the expression.
2499 -- The lower bound of the loop is the position after all
2500 -- previous positional components.
2502 Append_List
(Gen_Loop
(Add
(Nb_Elements
+ 1, To
=> Aggr_L
),
2504 Expression
(Assoc
)),
2507 -- Ada 2005 (AI-287)
2509 Append_List
(Gen_While
(Add
(Nb_Elements
, To
=> Aggr_L
),
2511 Get_Assoc_Expr
(Assoc
)),
2518 end Build_Array_Aggr_Code
;
2520 -------------------------------------
2521 -- Build_Assignment_With_Temporary --
2522 -------------------------------------
2524 function Build_Assignment_With_Temporary
2527 Source
: Node_Id
) return List_Id
2529 Loc
: constant Source_Ptr
:= Sloc
(Source
);
2531 Aggr_Code
: List_Id
;
2535 Aggr_Code
:= New_List
;
2537 Tmp
:= Build_Temporary_On_Secondary_Stack
(Loc
, Typ
, Aggr_Code
);
2539 Append_To
(Aggr_Code
,
2540 Make_OK_Assignment_Statement
(Loc
,
2542 Make_Explicit_Dereference
(Loc
,
2543 Prefix
=> New_Occurrence_Of
(Tmp
, Loc
)),
2544 Expression
=> Source
));
2546 Append_To
(Aggr_Code
,
2547 Make_OK_Assignment_Statement
(Loc
,
2550 Make_Explicit_Dereference
(Loc
,
2551 Prefix
=> New_Occurrence_Of
(Tmp
, Loc
))));
2554 end Build_Assignment_With_Temporary
;
2556 ----------------------------
2557 -- Build_Record_Aggr_Code --
2558 ----------------------------
2560 function Build_Record_Aggr_Code
2563 Lhs
: Node_Id
) return List_Id
2565 Loc
: constant Source_Ptr
:= Sloc
(N
);
2566 L
: constant List_Id
:= New_List
;
2567 N_Typ
: constant Entity_Id
:= Etype
(N
);
2573 Comp_Type
: Entity_Id
;
2574 Selector
: Entity_Id
;
2575 Comp_Expr
: Node_Id
;
2578 -- If this is an internal aggregate, the External_Final_List is an
2579 -- expression for the controller record of the enclosing type.
2581 -- If the current aggregate has several controlled components, this
2582 -- expression will appear in several calls to attach to the finali-
2583 -- zation list, and it must not be shared.
2585 Ancestor_Is_Expression
: Boolean := False;
2586 Ancestor_Is_Subtype_Mark
: Boolean := False;
2588 Init_Typ
: Entity_Id
:= Empty
;
2590 Finalization_Done
: Boolean := False;
2591 -- True if Generate_Finalization_Actions has already been called; calls
2592 -- after the first do nothing.
2594 function Ancestor_Discriminant_Value
(Disc
: Entity_Id
) return Node_Id
;
2595 -- Returns the value that the given discriminant of an ancestor type
2596 -- should receive (in the absence of a conflict with the value provided
2597 -- by an ancestor part of an extension aggregate).
2599 procedure Check_Ancestor_Discriminants
(Anc_Typ
: Entity_Id
);
2600 -- Check that each of the discriminant values defined by the ancestor
2601 -- part of an extension aggregate match the corresponding values
2602 -- provided by either an association of the aggregate or by the
2603 -- constraint imposed by a parent type (RM95-4.3.2(8)).
2605 function Compatible_Int_Bounds
2606 (Agg_Bounds
: Node_Id
;
2607 Typ_Bounds
: Node_Id
) return Boolean;
2608 -- Return true if Agg_Bounds are equal or within Typ_Bounds. It is
2609 -- assumed that both bounds are integer ranges.
2611 procedure Generate_Finalization_Actions
;
2612 -- Deal with the various controlled type data structure initializations
2613 -- (but only if it hasn't been done already).
2615 function Get_Constraint_Association
(T
: Entity_Id
) return Node_Id
;
2616 -- Returns the first discriminant association in the constraint
2617 -- associated with T, if any, otherwise returns Empty.
2619 function Get_Explicit_Discriminant_Value
(D
: Entity_Id
) return Node_Id
;
2620 -- If the ancestor part is an unconstrained type and further ancestors
2621 -- do not provide discriminants for it, check aggregate components for
2622 -- values of the discriminants.
2624 procedure Init_Hidden_Discriminants
(Typ
: Entity_Id
; List
: List_Id
);
2625 -- If Typ is derived, and constrains discriminants of the parent type,
2626 -- these discriminants are not components of the aggregate, and must be
2627 -- initialized. The assignments are appended to List. The same is done
2628 -- if Typ derives from an already constrained subtype of a discriminated
2631 procedure Init_Stored_Discriminants
;
2632 -- If the type is derived and has inherited discriminants, generate
2633 -- explicit assignments for each, using the store constraint of the
2634 -- type. Note that both visible and stored discriminants must be
2635 -- initialized in case the derived type has some renamed and some
2636 -- constrained discriminants.
2638 procedure Init_Visible_Discriminants
;
2639 -- If type has discriminants, retrieve their values from aggregate,
2640 -- and generate explicit assignments for each. This does not include
2641 -- discriminants inherited from ancestor, which are handled above.
2642 -- The type of the aggregate is a subtype created ealier using the
2643 -- given values of the discriminant components of the aggregate.
2645 procedure Initialize_Ctrl_Record_Component
2646 (Rec_Comp
: Node_Id
;
2647 Comp_Typ
: Entity_Id
;
2648 Init_Expr
: Node_Id
;
2650 -- Perform the initialization of controlled record component Rec_Comp.
2651 -- Comp_Typ is the component type. Init_Expr is the initialization
2652 -- expression for the record component. Hook-related declarations are
2653 -- inserted prior to aggregate N using Insert_Action. All remaining
2654 -- generated code is added to list Stmts.
2656 procedure Initialize_Record_Component
2657 (Rec_Comp
: Node_Id
;
2658 Comp_Typ
: Entity_Id
;
2659 Init_Expr
: Node_Id
;
2661 -- Perform the initialization of record component Rec_Comp. Comp_Typ
2662 -- is the component type. Init_Expr is the initialization expression
2663 -- of the record component. All generated code is added to list Stmts.
2665 function Is_Int_Range_Bounds
(Bounds
: Node_Id
) return Boolean;
2666 -- Check whether Bounds is a range node and its lower and higher bounds
2667 -- are integers literals.
2669 function Replace_Type
(Expr
: Node_Id
) return Traverse_Result
;
2670 -- If the aggregate contains a self-reference, traverse each expression
2671 -- to replace a possible self-reference with a reference to the proper
2672 -- component of the target of the assignment.
2674 function Rewrite_Discriminant
(Expr
: Node_Id
) return Traverse_Result
;
2675 -- If default expression of a component mentions a discriminant of the
2676 -- type, it must be rewritten as the discriminant of the target object.
2678 ---------------------------------
2679 -- Ancestor_Discriminant_Value --
2680 ---------------------------------
2682 function Ancestor_Discriminant_Value
(Disc
: Entity_Id
) return Node_Id
is
2684 Assoc_Elmt
: Elmt_Id
;
2685 Aggr_Comp
: Entity_Id
;
2686 Corresp_Disc
: Entity_Id
;
2687 Current_Typ
: Entity_Id
:= Base_Type
(Typ
);
2688 Parent_Typ
: Entity_Id
;
2689 Parent_Disc
: Entity_Id
;
2690 Save_Assoc
: Node_Id
:= Empty
;
2693 -- First check any discriminant associations to see if any of them
2694 -- provide a value for the discriminant.
2696 if Present
(Discriminant_Specifications
(Parent
(Current_Typ
))) then
2697 Assoc
:= First
(Component_Associations
(N
));
2698 while Present
(Assoc
) loop
2699 Aggr_Comp
:= Entity
(First
(Choices
(Assoc
)));
2701 if Ekind
(Aggr_Comp
) = E_Discriminant
then
2702 Save_Assoc
:= Expression
(Assoc
);
2704 Corresp_Disc
:= Corresponding_Discriminant
(Aggr_Comp
);
2705 while Present
(Corresp_Disc
) loop
2707 -- If found a corresponding discriminant then return the
2708 -- value given in the aggregate. (Note: this is not
2709 -- correct in the presence of side effects. ???)
2711 if Disc
= Corresp_Disc
then
2712 return Duplicate_Subexpr
(Expression
(Assoc
));
2715 Corresp_Disc
:= Corresponding_Discriminant
(Corresp_Disc
);
2723 -- No match found in aggregate, so chain up parent types to find
2724 -- a constraint that defines the value of the discriminant.
2726 Parent_Typ
:= Etype
(Current_Typ
);
2727 while Current_Typ
/= Parent_Typ
loop
2728 if Has_Discriminants
(Parent_Typ
)
2729 and then not Has_Unknown_Discriminants
(Parent_Typ
)
2731 Parent_Disc
:= First_Discriminant
(Parent_Typ
);
2733 -- We either get the association from the subtype indication
2734 -- of the type definition itself, or from the discriminant
2735 -- constraint associated with the type entity (which is
2736 -- preferable, but it's not always present ???)
2738 if Is_Empty_Elmt_List
(Discriminant_Constraint
(Current_Typ
))
2740 Assoc
:= Get_Constraint_Association
(Current_Typ
);
2741 Assoc_Elmt
:= No_Elmt
;
2744 First_Elmt
(Discriminant_Constraint
(Current_Typ
));
2745 Assoc
:= Node
(Assoc_Elmt
);
2748 -- Traverse the discriminants of the parent type looking
2749 -- for one that corresponds.
2751 while Present
(Parent_Disc
) and then Present
(Assoc
) loop
2752 Corresp_Disc
:= Parent_Disc
;
2753 while Present
(Corresp_Disc
)
2754 and then Disc
/= Corresp_Disc
2756 Corresp_Disc
:= Corresponding_Discriminant
(Corresp_Disc
);
2759 if Disc
= Corresp_Disc
then
2760 if Nkind
(Assoc
) = N_Discriminant_Association
then
2761 Assoc
:= Expression
(Assoc
);
2764 -- If the located association directly denotes
2765 -- a discriminant, then use the value of a saved
2766 -- association of the aggregate. This is an approach
2767 -- used to handle certain cases involving multiple
2768 -- discriminants mapped to a single discriminant of
2769 -- a descendant. It's not clear how to locate the
2770 -- appropriate discriminant value for such cases. ???
2772 if Is_Entity_Name
(Assoc
)
2773 and then Ekind
(Entity
(Assoc
)) = E_Discriminant
2775 Assoc
:= Save_Assoc
;
2778 return Duplicate_Subexpr
(Assoc
);
2781 Next_Discriminant
(Parent_Disc
);
2783 if No
(Assoc_Elmt
) then
2787 Next_Elmt
(Assoc_Elmt
);
2789 if Present
(Assoc_Elmt
) then
2790 Assoc
:= Node
(Assoc_Elmt
);
2798 Current_Typ
:= Parent_Typ
;
2799 Parent_Typ
:= Etype
(Current_Typ
);
2802 -- In some cases there's no ancestor value to locate (such as
2803 -- when an ancestor part given by an expression defines the
2804 -- discriminant value).
2807 end Ancestor_Discriminant_Value
;
2809 ----------------------------------
2810 -- Check_Ancestor_Discriminants --
2811 ----------------------------------
2813 procedure Check_Ancestor_Discriminants
(Anc_Typ
: Entity_Id
) is
2815 Disc_Value
: Node_Id
;
2819 Discr
:= First_Discriminant
(Base_Type
(Anc_Typ
));
2820 while Present
(Discr
) loop
2821 Disc_Value
:= Ancestor_Discriminant_Value
(Discr
);
2823 if Present
(Disc_Value
) then
2824 Cond
:= Make_Op_Ne
(Loc
,
2826 Make_Selected_Component
(Loc
,
2827 Prefix
=> New_Copy_Tree
(Target
),
2828 Selector_Name
=> New_Occurrence_Of
(Discr
, Loc
)),
2829 Right_Opnd
=> Disc_Value
);
2832 Make_Raise_Constraint_Error
(Loc
,
2834 Reason
=> CE_Discriminant_Check_Failed
));
2837 Next_Discriminant
(Discr
);
2839 end Check_Ancestor_Discriminants
;
2841 ---------------------------
2842 -- Compatible_Int_Bounds --
2843 ---------------------------
2845 function Compatible_Int_Bounds
2846 (Agg_Bounds
: Node_Id
;
2847 Typ_Bounds
: Node_Id
) return Boolean
2849 Agg_Lo
: constant Uint
:= Intval
(Low_Bound
(Agg_Bounds
));
2850 Agg_Hi
: constant Uint
:= Intval
(High_Bound
(Agg_Bounds
));
2851 Typ_Lo
: constant Uint
:= Intval
(Low_Bound
(Typ_Bounds
));
2852 Typ_Hi
: constant Uint
:= Intval
(High_Bound
(Typ_Bounds
));
2854 return Typ_Lo
<= Agg_Lo
and then Agg_Hi
<= Typ_Hi
;
2855 end Compatible_Int_Bounds
;
2857 -----------------------------------
2858 -- Generate_Finalization_Actions --
2859 -----------------------------------
2861 procedure Generate_Finalization_Actions
is
2863 -- Do the work only the first time this is called
2865 if Finalization_Done
then
2869 Finalization_Done
:= True;
2871 -- Determine the external finalization list. It is either the
2872 -- finalization list of the outer scope or the one coming from an
2873 -- outer aggregate. When the target is not a temporary, the proper
2874 -- scope is the scope of the target rather than the potentially
2875 -- transient current scope.
2877 if Is_Controlled
(Typ
) and then Ancestor_Is_Subtype_Mark
then
2878 Ref
:= Convert_To
(Init_Typ
, New_Copy_Tree
(Target
));
2879 Set_Assignment_OK
(Ref
);
2882 Make_Procedure_Call_Statement
(Loc
,
2885 (Find_Prim_Op
(Init_Typ
, Name_Initialize
), Loc
),
2886 Parameter_Associations
=> New_List
(New_Copy_Tree
(Ref
))));
2888 end Generate_Finalization_Actions
;
2890 --------------------------------
2891 -- Get_Constraint_Association --
2892 --------------------------------
2894 function Get_Constraint_Association
(T
: Entity_Id
) return Node_Id
is
2901 -- If type is private, get constraint from full view. This was
2902 -- previously done in an instance context, but is needed whenever
2903 -- the ancestor part has a discriminant, possibly inherited through
2904 -- multiple derivations.
2906 if Is_Private_Type
(Typ
) and then Present
(Full_View
(Typ
)) then
2907 Typ
:= Full_View
(Typ
);
2910 Indic
:= Subtype_Indication
(Type_Definition
(Parent
(Typ
)));
2912 -- Verify that the subtype indication carries a constraint
2914 if Nkind
(Indic
) = N_Subtype_Indication
2915 and then Present
(Constraint
(Indic
))
2917 return First
(Constraints
(Constraint
(Indic
)));
2921 end Get_Constraint_Association
;
2923 -------------------------------------
2924 -- Get_Explicit_Discriminant_Value --
2925 -------------------------------------
2927 function Get_Explicit_Discriminant_Value
2928 (D
: Entity_Id
) return Node_Id
2935 -- The aggregate has been normalized and all associations have a
2938 Assoc
:= First
(Component_Associations
(N
));
2939 while Present
(Assoc
) loop
2940 Choice
:= First
(Choices
(Assoc
));
2942 if Chars
(Choice
) = Chars
(D
) then
2943 Val
:= Expression
(Assoc
);
2952 end Get_Explicit_Discriminant_Value
;
2954 -------------------------------
2955 -- Init_Hidden_Discriminants --
2956 -------------------------------
2958 procedure Init_Hidden_Discriminants
(Typ
: Entity_Id
; List
: List_Id
) is
2959 function Is_Completely_Hidden_Discriminant
2960 (Discr
: Entity_Id
) return Boolean;
2961 -- Determine whether Discr is a completely hidden discriminant of
2964 ---------------------------------------
2965 -- Is_Completely_Hidden_Discriminant --
2966 ---------------------------------------
2968 function Is_Completely_Hidden_Discriminant
2969 (Discr
: Entity_Id
) return Boolean
2974 -- Use First/Next_Entity as First/Next_Discriminant do not yield
2975 -- completely hidden discriminants.
2977 Item
:= First_Entity
(Typ
);
2978 while Present
(Item
) loop
2979 if Ekind
(Item
) = E_Discriminant
2980 and then Is_Completely_Hidden
(Item
)
2981 and then Chars
(Original_Record_Component
(Item
)) =
2991 end Is_Completely_Hidden_Discriminant
;
2995 Base_Typ
: Entity_Id
;
2997 Discr_Constr
: Elmt_Id
;
2998 Discr_Init
: Node_Id
;
2999 Discr_Val
: Node_Id
;
3000 In_Aggr_Type
: Boolean;
3001 Par_Typ
: Entity_Id
;
3003 -- Start of processing for Init_Hidden_Discriminants
3006 -- The constraints on the hidden discriminants, if present, are kept
3007 -- in the Stored_Constraint list of the type itself, or in that of
3008 -- the base type. If not in the constraints of the aggregate itself,
3009 -- we examine ancestors to find discriminants that are not renamed
3010 -- by other discriminants but constrained explicitly.
3012 In_Aggr_Type
:= True;
3014 Base_Typ
:= Base_Type
(Typ
);
3015 while Is_Derived_Type
(Base_Typ
)
3017 (Present
(Stored_Constraint
(Base_Typ
))
3019 (In_Aggr_Type
and then Present
(Stored_Constraint
(Typ
))))
3021 Par_Typ
:= Etype
(Base_Typ
);
3023 if not Has_Discriminants
(Par_Typ
) then
3027 Discr
:= First_Discriminant
(Par_Typ
);
3029 -- We know that one of the stored-constraint lists is present
3031 if Present
(Stored_Constraint
(Base_Typ
)) then
3032 Discr_Constr
:= First_Elmt
(Stored_Constraint
(Base_Typ
));
3034 -- For private extension, stored constraint may be on full view
3036 elsif Is_Private_Type
(Base_Typ
)
3037 and then Present
(Full_View
(Base_Typ
))
3038 and then Present
(Stored_Constraint
(Full_View
(Base_Typ
)))
3041 First_Elmt
(Stored_Constraint
(Full_View
(Base_Typ
)));
3043 -- Otherwise, no discriminant to process
3046 Discr_Constr
:= No_Elmt
;
3049 while Present
(Discr
) and then Present
(Discr_Constr
) loop
3050 Discr_Val
:= Node
(Discr_Constr
);
3052 -- The parent discriminant is renamed in the derived type,
3053 -- nothing to initialize.
3055 -- type Deriv_Typ (Discr : ...)
3056 -- is new Parent_Typ (Discr => Discr);
3058 if Is_Entity_Name
(Discr_Val
)
3059 and then Ekind
(Entity
(Discr_Val
)) = E_Discriminant
3063 -- When the parent discriminant is constrained at the type
3064 -- extension level, it does not appear in the derived type.
3066 -- type Deriv_Typ (Discr : ...)
3067 -- is new Parent_Typ (Discr => Discr,
3068 -- Hidden_Discr => Expression);
3070 elsif Is_Completely_Hidden_Discriminant
(Discr
) then
3073 -- Otherwise initialize the discriminant
3077 Make_OK_Assignment_Statement
(Loc
,
3079 Make_Selected_Component
(Loc
,
3080 Prefix
=> New_Copy_Tree
(Target
),
3081 Selector_Name
=> New_Occurrence_Of
(Discr
, Loc
)),
3082 Expression
=> New_Copy_Tree
(Discr_Val
));
3084 Append_To
(List
, Discr_Init
);
3087 Next_Elmt
(Discr_Constr
);
3088 Next_Discriminant
(Discr
);
3091 In_Aggr_Type
:= False;
3092 Base_Typ
:= Base_Type
(Par_Typ
);
3094 end Init_Hidden_Discriminants
;
3096 --------------------------------
3097 -- Init_Visible_Discriminants --
3098 --------------------------------
3100 procedure Init_Visible_Discriminants
is
3101 Discriminant
: Entity_Id
;
3102 Discriminant_Value
: Node_Id
;
3105 Discriminant
:= First_Discriminant
(Typ
);
3106 while Present
(Discriminant
) loop
3108 Make_Selected_Component
(Loc
,
3109 Prefix
=> New_Copy_Tree
(Target
),
3110 Selector_Name
=> New_Occurrence_Of
(Discriminant
, Loc
));
3112 Discriminant_Value
:=
3113 Get_Discriminant_Value
3114 (Discriminant
, Typ
, Discriminant_Constraint
(N_Typ
));
3117 Make_OK_Assignment_Statement
(Loc
,
3119 Expression
=> New_Copy_Tree
(Discriminant_Value
));
3121 Append_To
(L
, Instr
);
3123 Next_Discriminant
(Discriminant
);
3125 end Init_Visible_Discriminants
;
3127 -------------------------------
3128 -- Init_Stored_Discriminants --
3129 -------------------------------
3131 procedure Init_Stored_Discriminants
is
3132 Discriminant
: Entity_Id
;
3133 Discriminant_Value
: Node_Id
;
3136 Discriminant
:= First_Stored_Discriminant
(Typ
);
3137 while Present
(Discriminant
) loop
3139 Make_Selected_Component
(Loc
,
3140 Prefix
=> New_Copy_Tree
(Target
),
3141 Selector_Name
=> New_Occurrence_Of
(Discriminant
, Loc
));
3143 Discriminant_Value
:=
3144 Get_Discriminant_Value
3145 (Discriminant
, N_Typ
, Discriminant_Constraint
(N_Typ
));
3148 Make_OK_Assignment_Statement
(Loc
,
3150 Expression
=> New_Copy_Tree
(Discriminant_Value
));
3152 Append_To
(L
, Instr
);
3154 Next_Stored_Discriminant
(Discriminant
);
3156 end Init_Stored_Discriminants
;
3158 --------------------------------------
3159 -- Initialize_Ctrl_Record_Component --
3160 --------------------------------------
3162 procedure Initialize_Ctrl_Record_Component
3163 (Rec_Comp
: Node_Id
;
3164 Comp_Typ
: Entity_Id
;
3165 Init_Expr
: Node_Id
;
3169 Hook_Clear
: Node_Id
;
3171 In_Place_Expansion
: Boolean;
3172 -- Flag set when a nonlimited controlled function call requires
3173 -- in-place expansion.
3176 -- Perform a preliminary analysis and resolution to determine what
3177 -- the initialization expression denotes. Unanalyzed function calls
3178 -- may appear as identifiers or indexed components.
3180 if Nkind
(Init_Expr
) in N_Function_Call
3182 | N_Indexed_Component
3183 and then not Analyzed
(Init_Expr
)
3185 Preanalyze_And_Resolve
(Init_Expr
, Comp_Typ
);
3188 In_Place_Expansion
:=
3189 Nkind
(Init_Expr
) = N_Function_Call
3190 and then not Is_Build_In_Place_Result_Type
(Comp_Typ
);
3192 -- The initialization expression is a controlled function call.
3193 -- Perform in-place removal of side effects to avoid creating a
3196 -- This in-place expansion is not performed for limited transient
3197 -- objects because the initialization is already done in place.
3199 if In_Place_Expansion
then
3201 -- Suppress the removal of side effects by general analysis
3202 -- because this behavior is emulated here. This avoids the
3203 -- generation of a transient scope, which leads to out-of-order
3204 -- adjustment and finalization.
3206 Set_No_Side_Effect_Removal
(Init_Expr
);
3208 -- Install all hook-related declarations and prepare the clean up
3209 -- statements. The generated code follows the initialization order
3210 -- of individual components and discriminants, rather than being
3211 -- inserted prior to the aggregate. This ensures that a transient
3212 -- component which mentions a discriminant has proper visibility
3213 -- of the discriminant.
3215 Process_Transient_Component
3217 Comp_Typ
=> Comp_Typ
,
3218 Init_Expr
=> Init_Expr
,
3219 Fin_Call
=> Fin_Call
,
3220 Hook_Clear
=> Hook_Clear
,
3224 -- Use the noncontrolled component initialization circuitry to
3225 -- assign the result of the function call to the record component.
3226 -- This also performs tag adjustment and [deep] adjustment of the
3227 -- record component.
3229 Initialize_Record_Component
3230 (Rec_Comp
=> Rec_Comp
,
3231 Comp_Typ
=> Comp_Typ
,
3232 Init_Expr
=> Init_Expr
,
3235 -- At this point the record component is fully initialized. Complete
3236 -- the processing of the controlled record component by finalizing
3237 -- the transient function result.
3239 if In_Place_Expansion
then
3240 Process_Transient_Component_Completion
3243 Fin_Call
=> Fin_Call
,
3244 Hook_Clear
=> Hook_Clear
,
3247 end Initialize_Ctrl_Record_Component
;
3249 ---------------------------------
3250 -- Initialize_Record_Component --
3251 ---------------------------------
3253 procedure Initialize_Record_Component
3254 (Rec_Comp
: Node_Id
;
3255 Comp_Typ
: Entity_Id
;
3256 Init_Expr
: Node_Id
;
3259 Exceptions_OK
: constant Boolean :=
3260 not Restriction_Active
(No_Exception_Propagation
);
3262 Finalization_OK
: constant Boolean := Needs_Finalization
(Comp_Typ
);
3264 Full_Typ
: constant Entity_Id
:= Underlying_Type
(Comp_Typ
);
3266 Blk_Stmts
: List_Id
;
3267 Init_Stmt
: Node_Id
;
3270 pragma Assert
(Nkind
(Init_Expr
) in N_Subexpr
);
3272 -- Protect the initialization statements from aborts. Generate:
3276 if Finalization_OK
and Abort_Allowed
then
3277 if Exceptions_OK
then
3278 Blk_Stmts
:= New_List
;
3283 Append_To
(Blk_Stmts
, Build_Runtime_Call
(Loc
, RE_Abort_Defer
));
3285 -- Otherwise aborts are not allowed. All generated code is added
3286 -- directly to the input list.
3292 -- Initialize the record component. Generate:
3294 -- Rec_Comp := Init_Expr;
3296 -- Note that the initialization expression is NOT replicated because
3297 -- only a single component may be initialized by it.
3300 Make_OK_Assignment_Statement
(Loc
,
3301 Name
=> New_Copy_Tree
(Rec_Comp
),
3302 Expression
=> Init_Expr
);
3303 Set_No_Ctrl_Actions
(Init_Stmt
);
3305 Append_To
(Blk_Stmts
, Init_Stmt
);
3307 -- Adjust the tag due to a possible view conversion. Generate:
3309 -- Rec_Comp._tag := Full_TypeP;
3311 if Tagged_Type_Expansion
and then Is_Tagged_Type
(Comp_Typ
) then
3312 Append_To
(Blk_Stmts
,
3313 Make_OK_Assignment_Statement
(Loc
,
3315 Make_Selected_Component
(Loc
,
3316 Prefix
=> New_Copy_Tree
(Rec_Comp
),
3319 (First_Tag_Component
(Full_Typ
), Loc
)),
3322 Unchecked_Convert_To
(RTE
(RE_Tag
),
3324 (Node
(First_Elmt
(Access_Disp_Table
(Full_Typ
))),
3328 -- Adjust the component. Generate:
3330 -- [Deep_]Adjust (Rec_Comp);
3333 and then not Is_Limited_Type
(Comp_Typ
)
3334 and then not Is_Build_In_Place_Function_Call
(Init_Expr
)
3338 (Obj_Ref
=> New_Copy_Tree
(Rec_Comp
),
3341 -- Guard against a missing [Deep_]Adjust when the component type
3342 -- was not properly frozen.
3344 if Present
(Adj_Call
) then
3345 Append_To
(Blk_Stmts
, Adj_Call
);
3349 -- Complete the protection of the initialization statements
3351 if Finalization_OK
and Abort_Allowed
then
3353 -- Wrap the initialization statements in a block to catch a
3354 -- potential exception. Generate:
3358 -- Rec_Comp := Init_Expr;
3359 -- Rec_Comp._tag := Full_TypP;
3360 -- [Deep_]Adjust (Rec_Comp);
3362 -- Abort_Undefer_Direct;
3365 if Exceptions_OK
then
3367 Build_Abort_Undefer_Block
(Loc
,
3371 -- Otherwise exceptions are not propagated. Generate:
3374 -- Rec_Comp := Init_Expr;
3375 -- Rec_Comp._tag := Full_TypP;
3376 -- [Deep_]Adjust (Rec_Comp);
3380 Append_To
(Blk_Stmts
,
3381 Build_Runtime_Call
(Loc
, RE_Abort_Undefer
));
3384 end Initialize_Record_Component
;
3386 -------------------------
3387 -- Is_Int_Range_Bounds --
3388 -------------------------
3390 function Is_Int_Range_Bounds
(Bounds
: Node_Id
) return Boolean is
3392 return Nkind
(Bounds
) = N_Range
3393 and then Nkind
(Low_Bound
(Bounds
)) = N_Integer_Literal
3394 and then Nkind
(High_Bound
(Bounds
)) = N_Integer_Literal
;
3395 end Is_Int_Range_Bounds
;
3401 function Replace_Type
(Expr
: Node_Id
) return Traverse_Result
is
3403 -- Note regarding the Root_Type test below: Aggregate components for
3404 -- self-referential types include attribute references to the current
3405 -- instance, of the form: Typ'access, etc.. These references are
3406 -- rewritten as references to the target of the aggregate: the
3407 -- left-hand side of an assignment, the entity in a declaration,
3408 -- or a temporary. Without this test, we would improperly extended
3409 -- this rewriting to attribute references whose prefix was not the
3410 -- type of the aggregate.
3412 if Nkind
(Expr
) = N_Attribute_Reference
3413 and then Is_Entity_Name
(Prefix
(Expr
))
3414 and then Is_Type
(Entity
(Prefix
(Expr
)))
3415 and then Root_Type
(Etype
(N
)) = Root_Type
(Entity
(Prefix
(Expr
)))
3417 if Is_Entity_Name
(Lhs
) then
3418 Rewrite
(Prefix
(Expr
), New_Occurrence_Of
(Entity
(Lhs
), Loc
));
3422 Make_Attribute_Reference
(Loc
,
3423 Attribute_Name
=> Name_Unrestricted_Access
,
3424 Prefix
=> New_Copy_Tree
(Lhs
)));
3425 Set_Analyzed
(Parent
(Expr
), False);
3432 --------------------------
3433 -- Rewrite_Discriminant --
3434 --------------------------
3436 function Rewrite_Discriminant
(Expr
: Node_Id
) return Traverse_Result
is
3438 if Is_Entity_Name
(Expr
)
3439 and then Present
(Entity
(Expr
))
3440 and then Ekind
(Entity
(Expr
)) = E_In_Parameter
3441 and then Present
(Discriminal_Link
(Entity
(Expr
)))
3442 and then Scope
(Discriminal_Link
(Entity
(Expr
))) =
3443 Base_Type
(Etype
(N
))
3446 Make_Selected_Component
(Loc
,
3447 Prefix
=> New_Copy_Tree
(Lhs
),
3448 Selector_Name
=> Make_Identifier
(Loc
, Chars
(Expr
))));
3450 -- The generated code will be reanalyzed, but if the reference
3451 -- to the discriminant appears within an already analyzed
3452 -- expression (e.g. a conditional) we must set its proper entity
3453 -- now. Context is an initialization procedure.
3459 end Rewrite_Discriminant
;
3461 procedure Replace_Discriminants
is
3462 new Traverse_Proc
(Rewrite_Discriminant
);
3464 procedure Replace_Self_Reference
is
3465 new Traverse_Proc
(Replace_Type
);
3467 -- Start of processing for Build_Record_Aggr_Code
3470 if Has_Self_Reference
(N
) then
3471 Replace_Self_Reference
(N
);
3474 -- If the target of the aggregate is class-wide, we must convert it
3475 -- to the actual type of the aggregate, so that the proper components
3476 -- are visible. We know already that the types are compatible.
3478 if Present
(Etype
(Lhs
))
3479 and then Is_Class_Wide_Type
(Etype
(Lhs
))
3481 Target
:= Unchecked_Convert_To
(Typ
, Lhs
);
3486 -- Deal with the ancestor part of extension aggregates or with the
3487 -- discriminants of the root type.
3489 if Nkind
(N
) = N_Extension_Aggregate
then
3491 Ancestor
: constant Node_Id
:= Ancestor_Part
(N
);
3496 -- If the ancestor part is a subtype mark "T", we generate
3498 -- init-proc (T (tmp)); if T is constrained and
3499 -- init-proc (S (tmp)); where S applies an appropriate
3500 -- constraint if T is unconstrained
3502 if Is_Entity_Name
(Ancestor
)
3503 and then Is_Type
(Entity
(Ancestor
))
3505 Ancestor_Is_Subtype_Mark
:= True;
3507 if Is_Constrained
(Entity
(Ancestor
)) then
3508 Init_Typ
:= Entity
(Ancestor
);
3510 -- For an ancestor part given by an unconstrained type mark,
3511 -- create a subtype constrained by appropriate corresponding
3512 -- discriminant values coming from either associations of the
3513 -- aggregate or a constraint on a parent type. The subtype will
3514 -- be used to generate the correct default value for the
3517 elsif Has_Discriminants
(Entity
(Ancestor
)) then
3519 Anc_Typ
: constant Entity_Id
:= Entity
(Ancestor
);
3520 Anc_Constr
: constant List_Id
:= New_List
;
3521 Discrim
: Entity_Id
;
3522 Disc_Value
: Node_Id
;
3523 New_Indic
: Node_Id
;
3524 Subt_Decl
: Node_Id
;
3527 Discrim
:= First_Discriminant
(Anc_Typ
);
3528 while Present
(Discrim
) loop
3529 Disc_Value
:= Ancestor_Discriminant_Value
(Discrim
);
3531 -- If no usable discriminant in ancestors, check
3532 -- whether aggregate has an explicit value for it.
3534 if No
(Disc_Value
) then
3536 Get_Explicit_Discriminant_Value
(Discrim
);
3539 Append_To
(Anc_Constr
, Disc_Value
);
3540 Next_Discriminant
(Discrim
);
3544 Make_Subtype_Indication
(Loc
,
3545 Subtype_Mark
=> New_Occurrence_Of
(Anc_Typ
, Loc
),
3547 Make_Index_Or_Discriminant_Constraint
(Loc
,
3548 Constraints
=> Anc_Constr
));
3550 Init_Typ
:= Create_Itype
(Ekind
(Anc_Typ
), N
);
3553 Make_Subtype_Declaration
(Loc
,
3554 Defining_Identifier
=> Init_Typ
,
3555 Subtype_Indication
=> New_Indic
);
3557 -- Itypes must be analyzed with checks off Declaration
3558 -- must have a parent for proper handling of subsidiary
3561 Set_Parent
(Subt_Decl
, N
);
3562 Analyze
(Subt_Decl
, Suppress
=> All_Checks
);
3566 Ref
:= Convert_To
(Init_Typ
, New_Copy_Tree
(Target
));
3567 Set_Assignment_OK
(Ref
);
3569 if not Is_Interface
(Init_Typ
) then
3571 Build_Initialization_Call
(Loc
,
3574 In_Init_Proc
=> Within_Init_Proc
,
3575 With_Default_Init
=> Has_Default_Init_Comps
(N
)
3577 Has_Task
(Base_Type
(Init_Typ
))));
3579 if Is_Constrained
(Entity
(Ancestor
))
3580 and then Has_Discriminants
(Entity
(Ancestor
))
3582 Check_Ancestor_Discriminants
(Entity
(Ancestor
));
3585 -- If ancestor type has Default_Initialization_Condition,
3586 -- add a DIC check after the ancestor object is initialized
3589 if Has_DIC
(Entity
(Ancestor
))
3590 and then Present
(DIC_Procedure
(Entity
(Ancestor
)))
3594 (Loc
, New_Copy_Tree
(Ref
), Entity
(Ancestor
)));
3598 -- Handle calls to C++ constructors
3600 elsif Is_CPP_Constructor_Call
(Ancestor
) then
3601 Init_Typ
:= Etype
(Ancestor
);
3602 Ref
:= Convert_To
(Init_Typ
, New_Copy_Tree
(Target
));
3603 Set_Assignment_OK
(Ref
);
3606 Build_Initialization_Call
(Loc
,
3609 In_Init_Proc
=> Within_Init_Proc
,
3610 With_Default_Init
=> Has_Default_Init_Comps
(N
),
3611 Constructor_Ref
=> Ancestor
));
3613 -- Ada 2005 (AI-287): If the ancestor part is an aggregate of
3614 -- limited type, a recursive call expands the ancestor. Note that
3615 -- in the limited case, the ancestor part must be either a
3616 -- function call (possibly qualified) or aggregate (definitely
3619 elsif Is_Limited_Type
(Etype
(Ancestor
))
3620 and then Nkind
(Unqualify
(Ancestor
)) in
3621 N_Aggregate | N_Extension_Aggregate
3623 Ancestor_Is_Expression
:= True;
3625 -- Set up finalization data for enclosing record, because
3626 -- controlled subcomponents of the ancestor part will be
3629 Generate_Finalization_Actions
;
3632 Build_Record_Aggr_Code
3633 (N
=> Unqualify
(Ancestor
),
3634 Typ
=> Etype
(Unqualify
(Ancestor
)),
3637 -- If the ancestor part is an expression "E", we generate
3641 -- In Ada 2005, this includes the case of a (possibly qualified)
3642 -- limited function call. The assignment will turn into a
3643 -- build-in-place function call (for further details, see
3644 -- Make_Build_In_Place_Call_In_Assignment).
3647 Ancestor_Is_Expression
:= True;
3648 Init_Typ
:= Etype
(Ancestor
);
3650 -- If the ancestor part is an aggregate, force its full
3651 -- expansion, which was delayed.
3653 if Nkind
(Unqualify
(Ancestor
)) in
3654 N_Aggregate | N_Extension_Aggregate
3656 Set_Analyzed
(Ancestor
, False);
3657 Set_Analyzed
(Expression
(Ancestor
), False);
3660 Ref
:= Convert_To
(Init_Typ
, New_Copy_Tree
(Target
));
3661 Set_Assignment_OK
(Ref
);
3663 -- Make the assignment without usual controlled actions, since
3664 -- we only want to Adjust afterwards, but not to Finalize
3665 -- beforehand. Add manual Adjust when necessary.
3667 Assign
:= New_List
(
3668 Make_OK_Assignment_Statement
(Loc
,
3670 Expression
=> Ancestor
));
3671 Set_No_Ctrl_Actions
(First
(Assign
));
3673 -- Assign the tag now to make sure that the dispatching call in
3674 -- the subsequent deep_adjust works properly (unless
3675 -- Tagged_Type_Expansion where tags are implicit).
3677 if Tagged_Type_Expansion
then
3679 Make_OK_Assignment_Statement
(Loc
,
3681 Make_Selected_Component
(Loc
,
3682 Prefix
=> New_Copy_Tree
(Target
),
3685 (First_Tag_Component
(Base_Type
(Typ
)), Loc
)),
3688 Unchecked_Convert_To
(RTE
(RE_Tag
),
3691 (Access_Disp_Table
(Base_Type
(Typ
)))),
3694 Set_Assignment_OK
(Name
(Instr
));
3695 Append_To
(Assign
, Instr
);
3697 -- Ada 2005 (AI-251): If tagged type has progenitors we must
3698 -- also initialize tags of the secondary dispatch tables.
3700 if Has_Interfaces
(Base_Type
(Typ
)) then
3702 (Typ
=> Base_Type
(Typ
),
3704 Stmts_List
=> Assign
,
3705 Init_Tags_List
=> Assign
);
3709 -- Call Adjust manually
3711 if Needs_Finalization
(Etype
(Ancestor
))
3712 and then not Is_Limited_Type
(Etype
(Ancestor
))
3713 and then not Is_Build_In_Place_Function_Call
(Ancestor
)
3717 (Obj_Ref
=> New_Copy_Tree
(Ref
),
3718 Typ
=> Etype
(Ancestor
));
3720 -- Guard against a missing [Deep_]Adjust when the ancestor
3721 -- type was not properly frozen.
3723 if Present
(Adj_Call
) then
3724 Append_To
(Assign
, Adj_Call
);
3729 Make_Unsuppress_Block
(Loc
, Name_Discriminant_Check
, Assign
));
3731 if Has_Discriminants
(Init_Typ
) then
3732 Check_Ancestor_Discriminants
(Init_Typ
);
3736 pragma Assert
(Nkind
(N
) = N_Extension_Aggregate
);
3738 (not (Ancestor_Is_Expression
and Ancestor_Is_Subtype_Mark
));
3741 -- Generate assignments of hidden discriminants. If the base type is
3742 -- an unchecked union, the discriminants are unknown to the back-end
3743 -- and absent from a value of the type, so assignments for them are
3746 if Has_Discriminants
(Typ
)
3747 and then not Is_Unchecked_Union
(Base_Type
(Typ
))
3749 Init_Hidden_Discriminants
(Typ
, L
);
3752 -- Normal case (not an extension aggregate)
3755 -- Generate the discriminant expressions, component by component.
3756 -- If the base type is an unchecked union, the discriminants are
3757 -- unknown to the back-end and absent from a value of the type, so
3758 -- assignments for them are not emitted.
3760 if Has_Discriminants
(Typ
)
3761 and then not Is_Unchecked_Union
(Base_Type
(Typ
))
3763 Init_Hidden_Discriminants
(Typ
, L
);
3765 -- Generate discriminant init values for the visible discriminants
3767 Init_Visible_Discriminants
;
3769 if Is_Derived_Type
(N_Typ
) then
3770 Init_Stored_Discriminants
;
3775 -- For CPP types we generate an implicit call to the C++ default
3776 -- constructor to ensure the proper initialization of the _Tag
3779 if Is_CPP_Class
(Root_Type
(Typ
)) and then CPP_Num_Prims
(Typ
) > 0 then
3780 Invoke_Constructor
: declare
3781 CPP_Parent
: constant Entity_Id
:= Enclosing_CPP_Parent
(Typ
);
3783 procedure Invoke_IC_Proc
(T
: Entity_Id
);
3784 -- Recursive routine used to climb to parents. Required because
3785 -- parents must be initialized before descendants to ensure
3786 -- propagation of inherited C++ slots.
3788 --------------------
3789 -- Invoke_IC_Proc --
3790 --------------------
3792 procedure Invoke_IC_Proc
(T
: Entity_Id
) is
3794 -- Avoid generating extra calls. Initialization required
3795 -- only for types defined from the level of derivation of
3796 -- type of the constructor and the type of the aggregate.
3798 if T
= CPP_Parent
then
3802 Invoke_IC_Proc
(Etype
(T
));
3804 -- Generate call to the IC routine
3806 if Present
(CPP_Init_Proc
(T
)) then
3808 Make_Procedure_Call_Statement
(Loc
,
3809 Name
=> New_Occurrence_Of
(CPP_Init_Proc
(T
), Loc
)));
3813 -- Start of processing for Invoke_Constructor
3816 -- Implicit invocation of the C++ constructor
3818 if Nkind
(N
) = N_Aggregate
then
3820 Make_Procedure_Call_Statement
(Loc
,
3822 New_Occurrence_Of
(Base_Init_Proc
(CPP_Parent
), Loc
),
3823 Parameter_Associations
=> New_List
(
3824 Unchecked_Convert_To
(CPP_Parent
,
3825 New_Copy_Tree
(Lhs
)))));
3828 Invoke_IC_Proc
(Typ
);
3829 end Invoke_Constructor
;
3832 -- Generate the assignments, component by component
3834 -- tmp.comp1 := Expr1_From_Aggr;
3835 -- tmp.comp2 := Expr2_From_Aggr;
3838 Comp
:= First
(Component_Associations
(N
));
3839 while Present
(Comp
) loop
3840 Selector
:= Entity
(First
(Choices
(Comp
)));
3841 pragma Assert
(Present
(Selector
));
3845 if Is_CPP_Constructor_Call
(Expression
(Comp
)) then
3847 Build_Initialization_Call
(Loc
,
3849 Make_Selected_Component
(Loc
,
3850 Prefix
=> New_Copy_Tree
(Target
),
3851 Selector_Name
=> New_Occurrence_Of
(Selector
, Loc
)),
3852 Typ
=> Etype
(Selector
),
3854 With_Default_Init
=> True,
3855 Constructor_Ref
=> Expression
(Comp
)));
3857 elsif Box_Present
(Comp
)
3858 and then Needs_Simple_Initialization
(Etype
(Selector
))
3861 Make_Selected_Component
(Loc
,
3862 Prefix
=> New_Copy_Tree
(Target
),
3863 Selector_Name
=> New_Occurrence_Of
(Selector
, Loc
));
3865 Initialize_Record_Component
3866 (Rec_Comp
=> Comp_Expr
,
3867 Comp_Typ
=> Etype
(Selector
),
3868 Init_Expr
=> Get_Simple_Init_Val
3869 (Typ
=> Etype
(Selector
),
3872 (if Known_Esize
(Selector
)
3873 then Esize
(Selector
)
3877 -- Ada 2005 (AI-287): For each default-initialized component generate
3878 -- a call to the corresponding IP subprogram if available.
3880 elsif Box_Present
(Comp
)
3881 and then Has_Non_Null_Base_Init_Proc
(Etype
(Selector
))
3883 if Ekind
(Selector
) /= E_Discriminant
then
3884 Generate_Finalization_Actions
;
3887 -- Ada 2005 (AI-287): If the component type has tasks then
3888 -- generate the activation chain and master entities (except
3889 -- in case of an allocator because in that case these entities
3890 -- are generated by Build_Task_Allocate_Block_With_Init_Stmts).
3893 Ctype
: constant Entity_Id
:= Etype
(Selector
);
3894 Inside_Allocator
: Boolean := False;
3895 P
: Node_Id
:= Parent
(N
);
3898 if Is_Task_Type
(Ctype
) or else Has_Task
(Ctype
) then
3899 while Present
(P
) loop
3900 if Nkind
(P
) = N_Allocator
then
3901 Inside_Allocator
:= True;
3908 if not Inside_Init_Proc
and not Inside_Allocator
then
3909 Build_Activation_Chain_Entity
(N
);
3915 Build_Initialization_Call
(Loc
,
3916 Id_Ref
=> Make_Selected_Component
(Loc
,
3917 Prefix
=> New_Copy_Tree
(Target
),
3919 New_Occurrence_Of
(Selector
, Loc
)),
3920 Typ
=> Etype
(Selector
),
3922 With_Default_Init
=> True));
3924 -- Prepare for component assignment
3926 elsif Ekind
(Selector
) /= E_Discriminant
3927 or else Nkind
(N
) = N_Extension_Aggregate
3929 -- All the discriminants have now been assigned
3931 -- This is now a good moment to initialize and attach all the
3932 -- controllers. Their position may depend on the discriminants.
3934 if Ekind
(Selector
) /= E_Discriminant
then
3935 Generate_Finalization_Actions
;
3938 Comp_Type
:= Underlying_Type
(Etype
(Selector
));
3940 Make_Selected_Component
(Loc
,
3941 Prefix
=> New_Copy_Tree
(Target
),
3942 Selector_Name
=> New_Occurrence_Of
(Selector
, Loc
));
3944 if Nkind
(Expression
(Comp
)) = N_Qualified_Expression
then
3945 Expr_Q
:= Expression
(Expression
(Comp
));
3947 Expr_Q
:= Expression
(Comp
);
3950 -- Now either create the assignment or generate the code for the
3951 -- inner aggregate top-down.
3953 if Is_Delayed_Aggregate
(Expr_Q
) then
3955 -- We have the following case of aggregate nesting inside
3956 -- an object declaration:
3958 -- type Arr_Typ is array (Integer range <>) of ...;
3960 -- type Rec_Typ (...) is record
3961 -- Obj_Arr_Typ : Arr_Typ (A .. B);
3964 -- Obj_Rec_Typ : Rec_Typ := (...,
3965 -- Obj_Arr_Typ => (X => (...), Y => (...)));
3967 -- The length of the ranges of the aggregate and Obj_Add_Typ
3968 -- are equal (B - A = Y - X), but they do not coincide (X /=
3969 -- A and B /= Y). This case requires array sliding which is
3970 -- performed in the following manner:
3972 -- subtype Arr_Sub is Arr_Typ (X .. Y);
3974 -- Temp (X) := (...);
3976 -- Temp (Y) := (...);
3977 -- Obj_Rec_Typ.Obj_Arr_Typ := Temp;
3979 if Ekind
(Comp_Type
) = E_Array_Subtype
3980 and then Is_Int_Range_Bounds
(Aggregate_Bounds
(Expr_Q
))
3981 and then Is_Int_Range_Bounds
(First_Index
(Comp_Type
))
3983 Compatible_Int_Bounds
3984 (Agg_Bounds
=> Aggregate_Bounds
(Expr_Q
),
3985 Typ_Bounds
=> First_Index
(Comp_Type
))
3987 -- Create the array subtype with bounds equal to those of
3988 -- the corresponding aggregate.
3991 SubE
: constant Entity_Id
:= Make_Temporary
(Loc
, 'T');
3993 SubD
: constant Node_Id
:=
3994 Make_Subtype_Declaration
(Loc
,
3995 Defining_Identifier
=> SubE
,
3996 Subtype_Indication
=>
3997 Make_Subtype_Indication
(Loc
,
3999 New_Occurrence_Of
(Etype
(Comp_Type
), Loc
),
4001 Make_Index_Or_Discriminant_Constraint
4003 Constraints
=> New_List
(
4005 (Aggregate_Bounds
(Expr_Q
))))));
4007 -- Create a temporary array of the above subtype which
4008 -- will be used to capture the aggregate assignments.
4010 TmpE
: constant Entity_Id
:= Make_Temporary
(Loc
, 'A', N
);
4012 TmpD
: constant Node_Id
:=
4013 Make_Object_Declaration
(Loc
,
4014 Defining_Identifier
=> TmpE
,
4015 Object_Definition
=> New_Occurrence_Of
(SubE
, Loc
));
4018 Set_No_Initialization
(TmpD
);
4019 Append_To
(L
, SubD
);
4020 Append_To
(L
, TmpD
);
4022 -- Expand aggregate into assignments to the temp array
4025 Late_Expansion
(Expr_Q
, Comp_Type
,
4026 New_Occurrence_Of
(TmpE
, Loc
)));
4031 Make_Assignment_Statement
(Loc
,
4032 Name
=> New_Copy_Tree
(Comp_Expr
),
4033 Expression
=> New_Occurrence_Of
(TmpE
, Loc
)));
4036 -- Normal case (sliding not required)
4040 Late_Expansion
(Expr_Q
, Comp_Type
, Comp_Expr
));
4043 -- Expr_Q is not delayed aggregate
4046 if Has_Discriminants
(Typ
) then
4047 Replace_Discriminants
(Expr_Q
);
4049 -- If the component is an array type that depends on
4050 -- discriminants, and the expression is a single Others
4051 -- clause, create an explicit subtype for it because the
4052 -- backend has troubles recovering the actual bounds.
4054 if Nkind
(Expr_Q
) = N_Aggregate
4055 and then Is_Array_Type
(Comp_Type
)
4056 and then Present
(Component_Associations
(Expr_Q
))
4059 Assoc
: constant Node_Id
:=
4060 First
(Component_Associations
(Expr_Q
));
4064 if Nkind
(First
(Choices
(Assoc
))) = N_Others_Choice
4067 Build_Actual_Subtype_Of_Component
4068 (Comp_Type
, Comp_Expr
);
4070 -- If the component type does not in fact depend on
4071 -- discriminants, the subtype declaration is empty.
4073 if Present
(Decl
) then
4074 Append_To
(L
, Decl
);
4075 Set_Etype
(Comp_Expr
, Defining_Entity
(Decl
));
4082 if Modify_Tree_For_C
4083 and then Nkind
(Expr_Q
) = N_Aggregate
4084 and then Is_Array_Type
(Etype
(Expr_Q
))
4085 and then Present
(First_Index
(Etype
(Expr_Q
)))
4088 Expr_Q_Type
: constant Entity_Id
:= Etype
(Expr_Q
);
4091 Build_Array_Aggr_Code
4093 Ctype
=> Component_Type
(Expr_Q_Type
),
4094 Index
=> First_Index
(Expr_Q_Type
),
4097 Is_Scalar_Type
(Component_Type
(Expr_Q_Type
))));
4101 -- Handle an initialization expression of a controlled type
4102 -- in case it denotes a function call. In general such a
4103 -- scenario will produce a transient scope, but this will
4104 -- lead to wrong order of initialization, adjustment, and
4105 -- finalization in the context of aggregates.
4107 -- Target.Comp := Ctrl_Func_Call;
4110 -- Trans_Obj : ... := Ctrl_Func_Call; -- object
4111 -- Target.Comp := Trans_Obj;
4112 -- Finalize (Trans_Obj);
4114 -- Target.Comp._tag := ...;
4115 -- Adjust (Target.Comp);
4117 -- In the example above, the call to Finalize occurs too
4118 -- early and as a result it may leave the record component
4119 -- in a bad state. Finalization of the transient object
4120 -- should really happen after adjustment.
4122 -- To avoid this scenario, perform in-place side-effect
4123 -- removal of the function call. This eliminates the
4124 -- transient property of the function result and ensures
4125 -- correct order of actions.
4127 -- Res : ... := Ctrl_Func_Call;
4128 -- Target.Comp := Res;
4129 -- Target.Comp._tag := ...;
4130 -- Adjust (Target.Comp);
4133 if Needs_Finalization
(Comp_Type
)
4134 and then Nkind
(Expr_Q
) /= N_Aggregate
4136 Initialize_Ctrl_Record_Component
4137 (Rec_Comp
=> Comp_Expr
,
4138 Comp_Typ
=> Etype
(Selector
),
4139 Init_Expr
=> Expr_Q
,
4142 -- Otherwise perform single component initialization
4145 Initialize_Record_Component
4146 (Rec_Comp
=> Comp_Expr
,
4147 Comp_Typ
=> Etype
(Selector
),
4148 Init_Expr
=> Expr_Q
,
4154 -- comment would be good here ???
4156 elsif Ekind
(Selector
) = E_Discriminant
4157 and then Nkind
(N
) /= N_Extension_Aggregate
4158 and then Nkind
(Parent
(N
)) = N_Component_Association
4159 and then Is_Constrained
(Typ
)
4161 -- We must check that the discriminant value imposed by the
4162 -- context is the same as the value given in the subaggregate,
4163 -- because after the expansion into assignments there is no
4164 -- record on which to perform a regular discriminant check.
4171 D_Val
:= First_Elmt
(Discriminant_Constraint
(Typ
));
4172 Disc
:= First_Discriminant
(Typ
);
4173 while Chars
(Disc
) /= Chars
(Selector
) loop
4174 Next_Discriminant
(Disc
);
4178 pragma Assert
(Present
(D_Val
));
4180 -- This check cannot performed for components that are
4181 -- constrained by a current instance, because this is not a
4182 -- value that can be compared with the actual constraint.
4184 if Nkind
(Node
(D_Val
)) /= N_Attribute_Reference
4185 or else not Is_Entity_Name
(Prefix
(Node
(D_Val
)))
4186 or else not Is_Type
(Entity
(Prefix
(Node
(D_Val
))))
4189 Make_Raise_Constraint_Error
(Loc
,
4192 Left_Opnd
=> New_Copy_Tree
(Node
(D_Val
)),
4193 Right_Opnd
=> Expression
(Comp
)),
4194 Reason
=> CE_Discriminant_Check_Failed
));
4197 -- Find self-reference in previous discriminant assignment,
4198 -- and replace with proper expression.
4205 while Present
(Ass
) loop
4206 if Nkind
(Ass
) = N_Assignment_Statement
4207 and then Nkind
(Name
(Ass
)) = N_Selected_Component
4208 and then Chars
(Selector_Name
(Name
(Ass
))) =
4212 (Ass
, New_Copy_Tree
(Expression
(Comp
)));
4222 -- If the component association was specified with a box and the
4223 -- component type has a Default_Initial_Condition, then generate
4224 -- a call to the DIC procedure.
4226 if Has_DIC
(Etype
(Selector
))
4227 and then Was_Default_Init_Box_Association
(Comp
)
4228 and then Present
(DIC_Procedure
(Etype
(Selector
)))
4231 Build_DIC_Call
(Loc
,
4232 Make_Selected_Component
(Loc
,
4233 Prefix
=> New_Copy_Tree
(Target
),
4234 Selector_Name
=> New_Occurrence_Of
(Selector
, Loc
)),
4241 -- If the type is tagged, the tag needs to be initialized (unless we
4242 -- are in VM-mode where tags are implicit). It is done late in the
4243 -- initialization process because in some cases, we call the init
4244 -- proc of an ancestor which will not leave out the right tag.
4246 if Ancestor_Is_Expression
then
4249 -- For CPP types we generated a call to the C++ default constructor
4250 -- before the components have been initialized to ensure the proper
4251 -- initialization of the _Tag component (see above).
4253 elsif Is_CPP_Class
(Typ
) then
4256 elsif Is_Tagged_Type
(Typ
) and then Tagged_Type_Expansion
then
4258 Make_OK_Assignment_Statement
(Loc
,
4260 Make_Selected_Component
(Loc
,
4261 Prefix
=> New_Copy_Tree
(Target
),
4264 (First_Tag_Component
(Base_Type
(Typ
)), Loc
)),
4267 Unchecked_Convert_To
(RTE
(RE_Tag
),
4269 (Node
(First_Elmt
(Access_Disp_Table
(Base_Type
(Typ
)))),
4272 Append_To
(L
, Instr
);
4274 -- Ada 2005 (AI-251): If the tagged type has been derived from an
4275 -- abstract interfaces we must also initialize the tags of the
4276 -- secondary dispatch tables.
4278 if Has_Interfaces
(Base_Type
(Typ
)) then
4280 (Typ
=> Base_Type
(Typ
),
4283 Init_Tags_List
=> L
);
4287 -- If the controllers have not been initialized yet (by lack of non-
4288 -- discriminant components), let's do it now.
4290 Generate_Finalization_Actions
;
4293 end Build_Record_Aggr_Code
;
4295 -------------------------------
4296 -- Convert_Aggr_In_Allocator --
4297 -------------------------------
4299 procedure Convert_Aggr_In_Allocator
4304 Loc
: constant Source_Ptr
:= Sloc
(Aggr
);
4305 Typ
: constant Entity_Id
:= Etype
(Aggr
);
4306 Temp
: constant Entity_Id
:= Defining_Identifier
(Decl
);
4308 Occ
: constant Node_Id
:=
4309 Unchecked_Convert_To
(Typ
,
4310 Make_Explicit_Dereference
(Loc
, New_Occurrence_Of
(Temp
, Loc
)));
4313 if Is_Array_Type
(Typ
) then
4314 Convert_Array_Aggr_In_Allocator
(Decl
, Aggr
, Occ
);
4316 elsif Has_Default_Init_Comps
(Aggr
) then
4318 L
: constant List_Id
:= New_List
;
4319 Init_Stmts
: List_Id
;
4322 Init_Stmts
:= Late_Expansion
(Aggr
, Typ
, Occ
);
4324 if Has_Task
(Typ
) then
4325 Build_Task_Allocate_Block_With_Init_Stmts
(L
, Aggr
, Init_Stmts
);
4326 Insert_Actions
(Alloc
, L
);
4328 Insert_Actions
(Alloc
, Init_Stmts
);
4333 Insert_Actions
(Alloc
, Late_Expansion
(Aggr
, Typ
, Occ
));
4335 end Convert_Aggr_In_Allocator
;
4337 --------------------------------
4338 -- Convert_Aggr_In_Assignment --
4339 --------------------------------
4341 procedure Convert_Aggr_In_Assignment
(N
: Node_Id
) is
4342 Aggr
: Node_Id
:= Expression
(N
);
4343 Typ
: constant Entity_Id
:= Etype
(Aggr
);
4344 Occ
: constant Node_Id
:= New_Copy_Tree
(Name
(N
));
4347 if Nkind
(Aggr
) = N_Qualified_Expression
then
4348 Aggr
:= Expression
(Aggr
);
4351 Insert_Actions_After
(N
, Late_Expansion
(Aggr
, Typ
, Occ
));
4352 end Convert_Aggr_In_Assignment
;
4354 ---------------------------------
4355 -- Convert_Aggr_In_Object_Decl --
4356 ---------------------------------
4358 procedure Convert_Aggr_In_Object_Decl
(N
: Node_Id
) is
4359 Obj
: constant Entity_Id
:= Defining_Identifier
(N
);
4360 Aggr
: Node_Id
:= Expression
(N
);
4361 Loc
: constant Source_Ptr
:= Sloc
(Aggr
);
4362 Typ
: constant Entity_Id
:= Etype
(Aggr
);
4363 Occ
: constant Node_Id
:= New_Occurrence_Of
(Obj
, Loc
);
4365 Has_Transient_Scope
: Boolean := False;
4367 function Discriminants_Ok
return Boolean;
4368 -- If the object type is constrained, the discriminants in the
4369 -- aggregate must be checked against the discriminants of the subtype.
4370 -- This cannot be done using Apply_Discriminant_Checks because after
4371 -- expansion there is no aggregate left to check.
4373 ----------------------
4374 -- Discriminants_Ok --
4375 ----------------------
4377 function Discriminants_Ok
return Boolean is
4378 Cond
: Node_Id
:= Empty
;
4387 D
:= First_Discriminant
(Typ
);
4388 Disc1
:= First_Elmt
(Discriminant_Constraint
(Typ
));
4389 Disc2
:= First_Elmt
(Discriminant_Constraint
(Etype
(Obj
)));
4390 while Present
(Disc1
) and then Present
(Disc2
) loop
4391 Val1
:= Node
(Disc1
);
4392 Val2
:= Node
(Disc2
);
4394 if not Is_OK_Static_Expression
(Val1
)
4395 or else not Is_OK_Static_Expression
(Val2
)
4397 Check
:= Make_Op_Ne
(Loc
,
4398 Left_Opnd
=> Duplicate_Subexpr
(Val1
),
4399 Right_Opnd
=> Duplicate_Subexpr
(Val2
));
4405 Cond
:= Make_Or_Else
(Loc
,
4407 Right_Opnd
=> Check
);
4410 elsif Expr_Value
(Val1
) /= Expr_Value
(Val2
) then
4411 Apply_Compile_Time_Constraint_Error
(Aggr
,
4412 Msg
=> "incorrect value for discriminant&??",
4413 Reason
=> CE_Discriminant_Check_Failed
,
4418 Next_Discriminant
(D
);
4423 -- If any discriminant constraint is nonstatic, emit a check
4425 if Present
(Cond
) then
4427 Make_Raise_Constraint_Error
(Loc
,
4429 Reason
=> CE_Discriminant_Check_Failed
));
4433 end Discriminants_Ok
;
4435 -- Start of processing for Convert_Aggr_In_Object_Decl
4438 Set_Assignment_OK
(Occ
);
4440 if Nkind
(Aggr
) = N_Qualified_Expression
then
4441 Aggr
:= Expression
(Aggr
);
4444 if Has_Discriminants
(Typ
)
4445 and then Typ
/= Etype
(Obj
)
4446 and then Is_Constrained
(Etype
(Obj
))
4447 and then not Discriminants_Ok
4452 -- If the context is an extended return statement, it has its own
4453 -- finalization machinery (i.e. works like a transient scope) and
4454 -- we do not want to create an additional one, because objects on
4455 -- the finalization list of the return must be moved to the caller's
4456 -- finalization list to complete the return.
4458 -- Similarly if the aggregate is limited, it is built in place, and the
4459 -- controlled components are not assigned to intermediate temporaries
4460 -- so there is no need for a transient scope in this case either.
4462 if Requires_Transient_Scope
(Typ
)
4463 and then Ekind
(Current_Scope
) /= E_Return_Statement
4464 and then not Is_Limited_Type
(Typ
)
4466 Establish_Transient_Scope
(Aggr
, Manage_Sec_Stack
=> False);
4467 Has_Transient_Scope
:= True;
4471 Stmts
: constant List_Id
:= Late_Expansion
(Aggr
, Typ
, Occ
);
4476 -- If Obj is already frozen or if N is wrapped in a transient scope,
4477 -- Stmts do not need to be saved in Initialization_Statements since
4478 -- there is no freezing issue.
4480 if Is_Frozen
(Obj
) or else Has_Transient_Scope
then
4481 Insert_Actions_After
(N
, Stmts
);
4483 Stmt
:= Make_Compound_Statement
(Sloc
(N
), Actions
=> Stmts
);
4484 Insert_Action_After
(N
, Stmt
);
4486 -- Insert_Action_After may freeze Obj in which case we should
4487 -- remove the compound statement just created and simply insert
4490 if Is_Frozen
(Obj
) then
4492 Insert_Actions_After
(N
, Stmts
);
4494 Set_Initialization_Statements
(Obj
, Stmt
);
4498 -- If Typ has controlled components and a call to a Slice_Assign
4499 -- procedure is part of the initialization statements, then we
4500 -- need to initialize the array component since Slice_Assign will
4501 -- need to adjust it.
4503 if Has_Controlled_Component
(Typ
) then
4504 Stmt
:= First
(Stmts
);
4506 while Present
(Stmt
) loop
4507 if Nkind
(Stmt
) = N_Procedure_Call_Statement
4508 and then Get_TSS_Name
(Entity
(Name
(Stmt
)))
4511 Param
:= First
(Parameter_Associations
(Stmt
));
4514 Build_Initialization_Call
4515 (Sloc
(N
), New_Copy_Tree
(Param
), Etype
(Param
)));
4523 Set_No_Initialization
(N
);
4525 -- After expansion the expression can be removed from the declaration
4526 -- except if the object is class-wide, in which case the aggregate
4527 -- provides the actual type.
4529 if not Is_Class_Wide_Type
(Etype
(Obj
)) then
4530 Set_Expression
(N
, Empty
);
4533 Initialize_Discriminants
(N
, Typ
);
4534 end Convert_Aggr_In_Object_Decl
;
4536 -------------------------------------
4537 -- Convert_Array_Aggr_In_Allocator --
4538 -------------------------------------
4540 procedure Convert_Array_Aggr_In_Allocator
4545 Typ
: constant Entity_Id
:= Etype
(Aggr
);
4546 Ctyp
: constant Entity_Id
:= Component_Type
(Typ
);
4547 Aggr_Code
: List_Id
;
4551 -- The target is an explicit dereference of the allocated object
4553 -- If the assignment can be done directly by the back end, then
4554 -- reset Set_Expansion_Delayed and do not expand further.
4556 if not CodePeer_Mode
4557 and then not Modify_Tree_For_C
4558 and then Aggr_Assignment_OK_For_Backend
(Aggr
)
4560 New_Aggr
:= New_Copy_Tree
(Aggr
);
4561 Set_Expansion_Delayed
(New_Aggr
, False);
4563 -- In the case of Target's type using the Designated_Storage_Model
4564 -- aspect with a Copy_To procedure, insert a temporary and have the
4565 -- back end handle the assignment to it. Copy the result to the
4568 if Has_Designated_Storage_Model_Aspect
4569 (Etype
(Prefix
(Expression
(Target
))))
4570 and then Present
(Storage_Model_Copy_To
4571 (Storage_Model_Object
4572 (Etype
(Prefix
(Expression
(Target
))))))
4575 Build_Assignment_With_Temporary
(Target
, Typ
, New_Aggr
);
4580 Make_OK_Assignment_Statement
(Sloc
(New_Aggr
),
4582 Expression
=> New_Aggr
));
4585 -- Or else, generate component assignments to it, as for an aggregate
4586 -- that appears on the right-hand side of an assignment statement.
4589 Build_Array_Aggr_Code
(Aggr
,
4591 Index
=> First_Index
(Typ
),
4593 Scalar_Comp
=> Is_Scalar_Type
(Ctyp
));
4596 Insert_Actions_After
(Decl
, Aggr_Code
);
4597 end Convert_Array_Aggr_In_Allocator
;
4599 ------------------------
4600 -- In_Place_Assign_OK --
4601 ------------------------
4603 function In_Place_Assign_OK
4605 Target_Object
: Entity_Id
:= Empty
) return Boolean
4607 Is_Array
: constant Boolean := Is_Array_Type
(Etype
(N
));
4610 Aggr_Bounds
: Range_Nodes
;
4612 Obj_Bounds
: Range_Nodes
;
4613 Parent_Kind
: Node_Kind
;
4614 Parent_Node
: Node_Id
;
4616 function Safe_Aggregate
(Aggr
: Node_Id
) return Boolean;
4617 -- Check recursively that each component of a (sub)aggregate does not
4618 -- depend on the variable being assigned to.
4620 function Safe_Component
(Expr
: Node_Id
) return Boolean;
4621 -- Verify that an expression cannot depend on the target being assigned
4622 -- to. Return true for compile-time known values, stand-alone objects,
4623 -- parameters passed by copy, calls to functions that return by copy,
4624 -- selected components thereof only if the aggregate's type is an array,
4625 -- indexed components and slices thereof only if the aggregate's type is
4626 -- a record, and simple expressions involving only these as operands.
4627 -- This is OK whatever the target because, for a component to overlap
4628 -- with the target, it must be either a direct reference to a component
4629 -- of the target, in which case there must be a matching selection or
4630 -- indexation or slicing, or an indirect reference to such a component,
4631 -- which is excluded by the above condition. Additionally, if the target
4632 -- is statically known, return true for arbitrarily nested selections,
4633 -- indexations or slicings, provided that their ultimate prefix is not
4634 -- the target itself.
4636 --------------------
4637 -- Safe_Aggregate --
4638 --------------------
4640 function Safe_Aggregate
(Aggr
: Node_Id
) return Boolean is
4644 if Nkind
(Parent
(Aggr
)) = N_Iterated_Component_Association
then
4648 if Present
(Expressions
(Aggr
)) then
4649 Expr
:= First
(Expressions
(Aggr
));
4650 while Present
(Expr
) loop
4651 if Nkind
(Expr
) = N_Aggregate
then
4652 if not Safe_Aggregate
(Expr
) then
4656 elsif not Safe_Component
(Expr
) then
4664 if Present
(Component_Associations
(Aggr
)) then
4665 Expr
:= First
(Component_Associations
(Aggr
));
4666 while Present
(Expr
) loop
4667 if Nkind
(Expression
(Expr
)) = N_Aggregate
then
4668 if not Safe_Aggregate
(Expression
(Expr
)) then
4672 -- If association has a box, no way to determine yet whether
4673 -- default can be assigned in place.
4675 elsif Box_Present
(Expr
) then
4678 elsif not Safe_Component
(Expression
(Expr
)) then
4689 --------------------
4690 -- Safe_Component --
4691 --------------------
4693 function Safe_Component
(Expr
: Node_Id
) return Boolean is
4694 Comp
: Node_Id
:= Expr
;
4696 function Check_Component
(C
: Node_Id
; T_OK
: Boolean) return Boolean;
4697 -- Do the recursive traversal, after copy. If T_OK is True, return
4698 -- True for a stand-alone object only if the target is statically
4699 -- known and distinct from the object. At the top level, we start
4700 -- with T_OK set to False and set it to True at a deeper level only
4701 -- if we cannot disambiguate the component here without statically
4702 -- knowing the target. Note that this is not optimal, we should do
4703 -- something along the lines of Denotes_Same_Prefix for that.
4705 ---------------------
4706 -- Check_Component --
4707 ---------------------
4709 function Check_Component
(C
: Node_Id
; T_OK
: Boolean) return Boolean
4712 function SDO
(E
: Entity_Id
) return Uint
;
4713 -- Return the Scope Depth Of the enclosing dynamic scope of E
4719 function SDO
(E
: Entity_Id
) return Uint
is
4721 return Scope_Depth
(Enclosing_Dynamic_Scope
(E
));
4724 -- Start of processing for Check_Component
4727 if Is_Overloaded
(C
) then
4730 elsif Compile_Time_Known_Value
(C
) then
4735 when N_Attribute_Reference
=>
4736 return Check_Component
(Prefix
(C
), T_OK
);
4738 when N_Function_Call
=>
4739 if Nkind
(Name
(C
)) = N_Explicit_Dereference
then
4740 return not Returns_By_Ref
(Etype
(Name
(C
)));
4742 return not Returns_By_Ref
(Entity
(Name
(C
)));
4745 when N_Indexed_Component | N_Slice
=>
4746 -- In a target record, these operations cannot determine
4747 -- alone a component so we can recurse whatever the target.
4748 return Check_Component
(Prefix
(C
), T_OK
or else Is_Array
);
4750 when N_Selected_Component
=>
4751 -- In a target array, this operation cannot determine alone
4752 -- a component so we can recurse whatever the target.
4754 Check_Component
(Prefix
(C
), T_OK
or else not Is_Array
);
4756 when N_Type_Conversion | N_Unchecked_Type_Conversion
=>
4757 return Check_Component
(Expression
(C
), T_OK
);
4760 return Check_Component
(Left_Opnd
(C
), T_OK
)
4761 and then Check_Component
(Right_Opnd
(C
), T_OK
);
4764 return Check_Component
(Right_Opnd
(C
), T_OK
);
4767 if Is_Entity_Name
(C
) and then Is_Object
(Entity
(C
)) then
4768 -- Case of a formal parameter component. It's either
4769 -- trivial if passed by copy or very annoying if not,
4770 -- because in the latter case it's almost equivalent
4771 -- to a dereference, so the path-based disambiguation
4772 -- logic is totally off and we always need the target.
4774 if Is_Formal
(Entity
(C
)) then
4776 -- If it is passed by copy, then this is safe
4778 if Mechanism
(Entity
(C
)) = By_Copy
then
4781 -- Otherwise, this is safe if the target is present
4782 -- and is at least as deeply nested as the component.
4785 return Present
(Target_Object
)
4786 and then not Is_Formal
(Target_Object
)
4787 and then SDO
(Target_Object
) >= SDO
(Entity
(C
));
4790 -- For a renamed object, recurse
4792 elsif Present
(Renamed_Object
(Entity
(C
))) then
4794 Check_Component
(Renamed_Object
(Entity
(C
)), T_OK
);
4796 -- If this is safe whatever the target, we are done
4801 -- If there is no target or the component is the target,
4802 -- this is not safe.
4804 elsif No
(Target_Object
)
4805 or else Entity
(C
) = Target_Object
4809 -- Case of a formal parameter target. This is safe if it
4810 -- is at most as deeply nested as the component.
4812 elsif Is_Formal
(Target_Object
) then
4813 return SDO
(Target_Object
) <= SDO
(Entity
(C
));
4815 -- For distinct stand-alone objects, this is safe
4821 -- For anything else than an object, this is not safe
4827 end Check_Component
;
4829 -- Start of processing for Safe_Component
4832 -- If the component appears in an association that may correspond
4833 -- to more than one element, it is not analyzed before expansion
4834 -- into assignments, to avoid side effects. We analyze, but do not
4835 -- resolve the copy, to obtain sufficient entity information for
4836 -- the checks that follow. If component is overloaded we assume
4837 -- an unsafe function call.
4839 if not Analyzed
(Comp
) then
4840 if Is_Overloaded
(Expr
) then
4843 elsif Nkind
(Expr
) = N_Allocator
then
4845 -- For now, too complex to analyze
4849 elsif Nkind
(Parent
(Expr
)) = N_Iterated_Component_Association
then
4851 -- Ditto for iterated component associations, which in general
4852 -- require an enclosing loop and involve nonstatic expressions.
4857 Comp
:= New_Copy_Tree
(Expr
);
4858 Set_Parent
(Comp
, Parent
(Expr
));
4862 if Nkind
(Comp
) = N_Aggregate
then
4863 return Safe_Aggregate
(Comp
);
4865 return Check_Component
(Comp
, False);
4869 -- Start of processing for In_Place_Assign_OK
4872 -- By-copy semantic cannot be guaranteed for controlled objects
4874 if Needs_Finalization
(Etype
(N
)) then
4878 Parent_Node
:= Parent
(N
);
4879 Parent_Kind
:= Nkind
(Parent_Node
);
4881 if Parent_Kind
= N_Qualified_Expression
then
4882 Parent_Node
:= Parent
(Parent_Node
);
4883 Parent_Kind
:= Nkind
(Parent_Node
);
4886 -- On assignment, sliding can take place, so we cannot do the
4887 -- assignment in place unless the bounds of the aggregate are
4888 -- statically equal to those of the target.
4890 -- If the aggregate is given by an others choice, the bounds are
4891 -- derived from the left-hand side, and the assignment is safe if
4892 -- the expression is.
4895 and then Present
(Component_Associations
(N
))
4896 and then not Is_Others_Aggregate
(N
)
4898 Aggr_In
:= First_Index
(Etype
(N
));
4900 -- Context is an assignment
4902 if Parent_Kind
= N_Assignment_Statement
then
4903 Obj_In
:= First_Index
(Etype
(Name
(Parent_Node
)));
4905 -- Context is an allocator. Check the bounds of the aggregate against
4906 -- those of the designated type, except in the case where the type is
4907 -- unconstrained (and then we can directly return true, see below).
4909 else pragma Assert
(Parent_Kind
= N_Allocator
);
4911 Desig_Typ
: constant Entity_Id
:=
4912 Designated_Type
(Etype
(Parent_Node
));
4914 if not Is_Constrained
(Desig_Typ
) then
4918 Obj_In
:= First_Index
(Desig_Typ
);
4922 while Present
(Aggr_In
) loop
4923 Aggr_Bounds
:= Get_Index_Bounds
(Aggr_In
);
4924 Obj_Bounds
:= Get_Index_Bounds
(Obj_In
);
4926 -- We require static bounds for the target and a static matching
4927 -- of low bound for the aggregate.
4929 if not Compile_Time_Known_Value
(Obj_Bounds
.First
)
4930 or else not Compile_Time_Known_Value
(Obj_Bounds
.Last
)
4931 or else not Compile_Time_Known_Value
(Aggr_Bounds
.First
)
4932 or else Expr_Value
(Aggr_Bounds
.First
) /=
4933 Expr_Value
(Obj_Bounds
.First
)
4937 -- For an assignment statement we require static matching of
4938 -- bounds. Ditto for an allocator whose qualified expression
4939 -- is a constrained type. If the expression in the allocator
4940 -- is an unconstrained array, we accept an upper bound that
4941 -- is not static, to allow for nonstatic expressions of the
4942 -- base type. Clearly there are further possibilities (with
4943 -- diminishing returns) for safely building arrays in place
4946 elsif Parent_Kind
= N_Assignment_Statement
4947 or else Is_Constrained
(Etype
(Parent_Node
))
4949 if not Compile_Time_Known_Value
(Aggr_Bounds
.Last
)
4950 or else Expr_Value
(Aggr_Bounds
.Last
) /=
4951 Expr_Value
(Obj_Bounds
.Last
)
4957 Next_Index
(Aggr_In
);
4958 Next_Index
(Obj_In
);
4962 -- Now check the component values themselves, except for an allocator
4963 -- for which the target is newly allocated memory.
4965 if Parent_Kind
= N_Allocator
then
4968 return Safe_Aggregate
(N
);
4970 end In_Place_Assign_OK
;
4972 ----------------------------
4973 -- Convert_To_Assignments --
4974 ----------------------------
4976 procedure Convert_To_Assignments
(N
: Node_Id
; Typ
: Entity_Id
) is
4977 Loc
: constant Source_Ptr
:= Sloc
(N
);
4981 Aggr_Code
: List_Id
;
4983 Target_Expr
: Node_Id
;
4984 Parent_Kind
: Node_Kind
;
4985 Unc_Decl
: Boolean := False;
4986 Parent_Node
: Node_Id
;
4989 pragma Assert
(Nkind
(N
) in N_Aggregate | N_Extension_Aggregate
);
4990 pragma Assert
(not Is_Static_Dispatch_Table_Aggregate
(N
));
4991 pragma Assert
(Is_Record_Type
(Typ
));
4993 Parent_Node
:= Parent
(N
);
4994 Parent_Kind
:= Nkind
(Parent_Node
);
4996 if Parent_Kind
= N_Qualified_Expression
then
4997 -- Check if we are in an unconstrained declaration because in this
4998 -- case the current delayed expansion mechanism doesn't work when
4999 -- the declared object size depends on the initializing expr.
5001 Parent_Node
:= Parent
(Parent_Node
);
5002 Parent_Kind
:= Nkind
(Parent_Node
);
5004 if Parent_Kind
= N_Object_Declaration
then
5006 not Is_Entity_Name
(Object_Definition
(Parent_Node
))
5007 or else (Nkind
(N
) = N_Aggregate
5010 (Entity
(Object_Definition
(Parent_Node
))))
5011 or else Is_Class_Wide_Type
5012 (Entity
(Object_Definition
(Parent_Node
)));
5016 -- Just set the Delay flag in the cases where the transformation will be
5017 -- done top down from above.
5020 -- Internal aggregate (transformed when expanding the parent)
5023 N_Aggregate | N_Extension_Aggregate | N_Component_Association
5025 -- Allocator (see Convert_Aggr_In_Allocator)
5027 or else Parent_Kind
= N_Allocator
5029 -- Object declaration (see Convert_Aggr_In_Object_Decl)
5031 or else (Parent_Kind
= N_Object_Declaration
and then not Unc_Decl
)
5033 -- Safe assignment (see Convert_Aggr_Assignments). So far only the
5034 -- assignments in init procs are taken into account.
5036 or else (Parent_Kind
= N_Assignment_Statement
5037 and then Inside_Init_Proc
)
5039 -- (Ada 2005) An inherently limited type in a return statement, which
5040 -- will be handled in a build-in-place fashion, and may be rewritten
5041 -- as an extended return and have its own finalization machinery.
5042 -- In the case of a simple return, the aggregate needs to be delayed
5043 -- until the scope for the return statement has been created, so
5044 -- that any finalization chain will be associated with that scope.
5045 -- For extended returns, we delay expansion to avoid the creation
5046 -- of an unwanted transient scope that could result in premature
5047 -- finalization of the return object (which is built in place
5048 -- within the caller's scope).
5050 or else Is_Build_In_Place_Aggregate_Return
(N
)
5052 Set_Expansion_Delayed
(N
);
5056 -- Otherwise, if a transient scope is required, create it now. If we
5057 -- are within an initialization procedure do not create such, because
5058 -- the target of the assignment must not be declared within a local
5059 -- block, and because cleanup will take place on return from the
5060 -- initialization procedure.
5062 -- Should the condition be more restrictive ???
5064 if Requires_Transient_Scope
(Typ
) and then not Inside_Init_Proc
then
5065 Establish_Transient_Scope
(N
, Manage_Sec_Stack
=> False);
5068 -- If the aggregate is nonlimited, create a temporary, since aggregates
5069 -- have "by copy" semantics. If it is limited and context is an
5070 -- assignment, this is a subaggregate for an enclosing aggregate being
5071 -- expanded. It must be built in place, so use target of the current
5074 if Is_Limited_Type
(Typ
)
5075 and then Parent_Kind
= N_Assignment_Statement
5077 Target_Expr
:= New_Copy_Tree
(Name
(Parent_Node
));
5078 Insert_Actions
(Parent_Node
,
5079 Build_Record_Aggr_Code
(N
, Typ
, Target_Expr
));
5080 Rewrite
(Parent_Node
, Make_Null_Statement
(Loc
));
5082 -- Do not declare a temporary to initialize an aggregate assigned to
5083 -- a target when in-place assignment is possible, i.e. preserving the
5084 -- by-copy semantic of aggregates. This avoids large stack usage and
5085 -- generates more efficient code.
5087 elsif Parent_Kind
= N_Assignment_Statement
5088 and then In_Place_Assign_OK
(N
, Get_Base_Object
(Name
(Parent_Node
)))
5091 Lhs
: constant Node_Id
:= Name
(Parent_Node
);
5093 -- Apply discriminant check if required
5095 if Has_Discriminants
(Etype
(N
)) then
5096 Apply_Discriminant_Check
(N
, Etype
(Lhs
), Lhs
);
5099 -- The check just above may have replaced the aggregate with a CE
5101 if Nkind
(N
) in N_Aggregate | N_Extension_Aggregate
then
5102 Target_Expr
:= New_Copy_Tree
(Lhs
);
5103 Insert_Actions
(Parent_Node
,
5104 Build_Record_Aggr_Code
(N
, Typ
, Target_Expr
));
5105 Rewrite
(Parent_Node
, Make_Null_Statement
(Loc
));
5110 Temp
:= Make_Temporary
(Loc
, 'A', N
);
5112 -- If the type inherits unknown discriminants, use the view with
5113 -- known discriminants if available.
5115 if Has_Unknown_Discriminants
(Typ
)
5116 and then Present
(Underlying_Record_View
(Typ
))
5118 T
:= Underlying_Record_View
(Typ
);
5124 Make_Object_Declaration
(Loc
,
5125 Defining_Identifier
=> Temp
,
5126 Object_Definition
=> New_Occurrence_Of
(T
, Loc
));
5128 Set_No_Initialization
(Instr
);
5129 Insert_Action
(N
, Instr
);
5130 Initialize_Discriminants
(Instr
, T
);
5132 Target_Expr
:= New_Occurrence_Of
(Temp
, Loc
);
5133 Aggr_Code
:= Build_Record_Aggr_Code
(N
, T
, Target_Expr
);
5135 -- Save the last assignment statement associated with the aggregate
5136 -- when building a controlled object. This reference is utilized by
5137 -- the finalization machinery when marking an object as successfully
5140 if Needs_Finalization
(T
) then
5141 Set_Last_Aggregate_Assignment
(Temp
, Last
(Aggr_Code
));
5144 Insert_Actions
(N
, Aggr_Code
);
5145 Rewrite
(N
, New_Occurrence_Of
(Temp
, Loc
));
5146 Analyze_And_Resolve
(N
, T
);
5148 end Convert_To_Assignments
;
5150 ---------------------------
5151 -- Convert_To_Positional --
5152 ---------------------------
5154 procedure Convert_To_Positional
5156 Handle_Bit_Packed
: Boolean := False)
5158 Typ
: constant Entity_Id
:= Etype
(N
);
5159 Dims
: constant Nat
:= Number_Dimensions
(Typ
);
5160 Max_Others_Replicate
: constant Nat
:= Max_Aggregate_Size
(N
);
5162 Static_Components
: Boolean := True;
5164 procedure Check_Static_Components
;
5165 -- Check whether all components of the aggregate are compile-time known
5166 -- values, and can be passed as is to the back-end without further
5173 Ixb
: Node_Id
) return Boolean;
5174 -- Convert the aggregate into a purely positional form if possible after
5175 -- checking that the bounds of all dimensions are known to be static.
5177 function Is_Flat
(N
: Node_Id
; Dims
: Nat
) return Boolean;
5178 -- Return True if the aggregate N is flat (which is not trivial in the
5179 -- case of multidimensional aggregates).
5181 function Is_Static_Element
(N
: Node_Id
; Dims
: Nat
) return Boolean;
5182 -- Return True if N, an element of a component association list, i.e.
5183 -- N_Component_Association or N_Iterated_Component_Association, has a
5184 -- compile-time known value and can be passed as is to the back-end
5185 -- without further expansion.
5186 -- An Iterated_Component_Association is treated as nonstatic in most
5187 -- cases for now, so there are possibilities for optimization.
5189 -----------------------------
5190 -- Check_Static_Components --
5191 -----------------------------
5193 -- Could use some comments in this body ???
5195 procedure Check_Static_Components
is
5200 Static_Components
:= True;
5202 if Nkind
(N
) = N_String_Literal
then
5205 elsif Present
(Expressions
(N
)) then
5206 Expr
:= First
(Expressions
(N
));
5207 while Present
(Expr
) loop
5208 if Nkind
(Expr
) /= N_Aggregate
5209 or else not Compile_Time_Known_Aggregate
(Expr
)
5210 or else Expansion_Delayed
(Expr
)
5212 Static_Components
:= False;
5220 if Nkind
(N
) = N_Aggregate
5221 and then Present
(Component_Associations
(N
))
5223 Assoc
:= First
(Component_Associations
(N
));
5224 while Present
(Assoc
) loop
5225 if not Is_Static_Element
(Assoc
, Dims
) then
5226 Static_Components
:= False;
5233 end Check_Static_Components
;
5243 Ixb
: Node_Id
) return Boolean
5245 Loc
: constant Source_Ptr
:= Sloc
(N
);
5246 Blo
: constant Node_Id
:= Type_Low_Bound
(Etype
(Ixb
));
5247 Lo
: constant Node_Id
:= Type_Low_Bound
(Etype
(Ix
));
5248 Hi
: constant Node_Id
:= Type_High_Bound
(Etype
(Ix
));
5250 function Cannot_Flatten_Next_Aggr
(Expr
: Node_Id
) return Boolean;
5251 -- Return true if Expr is an aggregate for the next dimension that
5252 -- cannot be recursively flattened.
5254 ------------------------------
5255 -- Cannot_Flatten_Next_Aggr --
5256 ------------------------------
5258 function Cannot_Flatten_Next_Aggr
(Expr
: Node_Id
) return Boolean is
5260 return Nkind
(Expr
) = N_Aggregate
5261 and then Present
(Next_Index
(Ix
))
5263 Flatten
(Expr
, Dims
- 1, Next_Index
(Ix
), Next_Index
(Ixb
));
5264 end Cannot_Flatten_Next_Aggr
;
5270 Others_Present
: Boolean;
5272 -- Start of processing for Flatten
5275 if Nkind
(Original_Node
(N
)) = N_String_Literal
then
5279 if not Compile_Time_Known_Value
(Lo
)
5280 or else not Compile_Time_Known_Value
(Hi
)
5285 Lov
:= Expr_Value
(Lo
);
5286 Hiv
:= Expr_Value
(Hi
);
5288 -- Check if there is an others choice
5290 Others_Present
:= False;
5292 if Present
(Component_Associations
(N
)) then
5293 if Is_Empty_List
(Component_Associations
(N
)) then
5294 -- an expanded null array aggregate
5303 Assoc
:= First
(Component_Associations
(N
));
5304 while Present
(Assoc
) loop
5306 -- If this is a box association, flattening is in general
5307 -- not possible because at this point we cannot tell if the
5308 -- default is static or even exists.
5310 if Box_Present
(Assoc
) then
5313 elsif Nkind
(Assoc
) = N_Iterated_Component_Association
then
5317 Choice
:= First
(Choice_List
(Assoc
));
5319 while Present
(Choice
) loop
5320 if Nkind
(Choice
) = N_Others_Choice
then
5321 Others_Present
:= True;
5332 -- If the low bound is not known at compile time and others is not
5333 -- present we can proceed since the bounds can be obtained from the
5337 or else (not Compile_Time_Known_Value
(Blo
) and then Others_Present
)
5342 -- Determine if set of alternatives is suitable for conversion and
5343 -- build an array containing the values in sequence.
5346 Vals
: array (UI_To_Int
(Lov
) .. UI_To_Int
(Hiv
))
5347 of Node_Id
:= (others => Empty
);
5348 -- The values in the aggregate sorted appropriately
5351 -- Same data as Vals in list form
5354 -- Used to validate Max_Others_Replicate limit
5358 Num
: Int
:= UI_To_Int
(Lov
);
5364 if Present
(Expressions
(N
)) then
5365 Elmt
:= First
(Expressions
(N
));
5366 while Present
(Elmt
) loop
5367 -- In the case of a multidimensional array, check that the
5368 -- aggregate can be recursively flattened.
5370 if Cannot_Flatten_Next_Aggr
(Elmt
) then
5374 -- Duplicate expression for each index it covers
5376 Vals
(Num
) := New_Copy_Tree
(Elmt
);
5383 if No
(Component_Associations
(N
)) then
5387 Elmt
:= First
(Component_Associations
(N
));
5389 Component_Loop
: while Present
(Elmt
) loop
5390 Expr
:= Expression
(Elmt
);
5392 -- In the case of a multidimensional array, check that the
5393 -- aggregate can be recursively flattened.
5395 if Cannot_Flatten_Next_Aggr
(Expr
) then
5399 Choice
:= First
(Choice_List
(Elmt
));
5400 Choice_Loop
: while Present
(Choice
) loop
5402 -- If we have an others choice, fill in the missing elements
5403 -- subject to the limit established by Max_Others_Replicate.
5405 if Nkind
(Choice
) = N_Others_Choice
then
5408 -- If the expression involves a construct that generates
5409 -- a loop, we must generate individual assignments and
5410 -- no flattening is possible.
5412 if Nkind
(Expr
) = N_Quantified_Expression
then
5416 for J
in Vals
'Range loop
5417 if No
(Vals
(J
)) then
5418 Vals
(J
) := New_Copy_Tree
(Expr
);
5419 Rep_Count
:= Rep_Count
+ 1;
5421 -- Check for maximum others replication. Note that
5422 -- we skip this test if either of the restrictions
5423 -- No_Implicit_Loops or No_Elaboration_Code is
5424 -- active, if this is a preelaborable unit or
5425 -- a predefined unit, or if the unit must be
5426 -- placed in data memory. This also ensures that
5427 -- predefined units get the same level of constant
5428 -- folding in Ada 95 and Ada 2005, where their
5429 -- categorization has changed.
5432 P
: constant Entity_Id
:=
5433 Cunit_Entity
(Current_Sem_Unit
);
5436 -- Check if duplication is always OK and, if so,
5437 -- continue processing.
5439 if Restriction_Active
(No_Implicit_Loops
) then
5442 -- If duplication is not always OK, continue
5443 -- only if either the element is static or is
5444 -- an aggregate (we already know it is OK).
5446 elsif not Is_Static_Element
(Elmt
, Dims
)
5447 and then Nkind
(Expr
) /= N_Aggregate
5451 -- Check if duplication is OK for elaboration
5452 -- purposes and, if so, continue processing.
5454 elsif Restriction_Active
(No_Elaboration_Code
)
5456 (Ekind
(Current_Scope
) = E_Package
5458 Static_Elaboration_Desired
(Current_Scope
))
5459 or else Is_Preelaborated
(P
)
5460 or else (Ekind
(P
) = E_Package_Body
5462 Is_Preelaborated
(Spec_Entity
(P
)))
5464 Is_Predefined_Unit
(Get_Source_Unit
(P
))
5468 -- Otherwise, check that the replication count
5471 elsif Rep_Count
> Max_Others_Replicate
then
5479 and then Warn_On_Redundant_Constructs
5481 Error_Msg_N
("there are no others?r?", Elmt
);
5484 exit Component_Loop
;
5486 -- Case of a subtype mark, identifier or expanded name
5488 elsif Is_Entity_Name
(Choice
)
5489 and then Is_Type
(Entity
(Choice
))
5491 Lo
:= Type_Low_Bound
(Etype
(Choice
));
5492 Hi
:= Type_High_Bound
(Etype
(Choice
));
5494 -- Case of subtype indication
5496 elsif Nkind
(Choice
) = N_Subtype_Indication
then
5497 Lo
:= Low_Bound
(Range_Expression
(Constraint
(Choice
)));
5498 Hi
:= High_Bound
(Range_Expression
(Constraint
(Choice
)));
5502 elsif Nkind
(Choice
) = N_Range
then
5503 Lo
:= Low_Bound
(Choice
);
5504 Hi
:= High_Bound
(Choice
);
5506 -- Normal subexpression case
5508 else pragma Assert
(Nkind
(Choice
) in N_Subexpr
);
5509 if not Compile_Time_Known_Value
(Choice
) then
5513 Choice_Index
:= UI_To_Int
(Expr_Value
(Choice
));
5515 if Choice_Index
in Vals
'Range then
5516 Vals
(Choice_Index
) := New_Copy_Tree
(Expr
);
5519 -- Choice is statically out-of-range, will be
5520 -- rewritten to raise Constraint_Error.
5528 -- Range cases merge with Lo,Hi set
5530 if not Compile_Time_Known_Value
(Lo
)
5532 not Compile_Time_Known_Value
(Hi
)
5537 for J
in UI_To_Int
(Expr_Value
(Lo
)) ..
5538 UI_To_Int
(Expr_Value
(Hi
))
5540 Vals
(J
) := New_Copy_Tree
(Expr
);
5546 end loop Choice_Loop
;
5549 end loop Component_Loop
;
5551 -- If we get here the conversion is possible
5554 for J
in Vals
'Range loop
5555 Append
(Vals
(J
), Vlist
);
5558 Rewrite
(N
, Make_Aggregate
(Loc
, Expressions
=> Vlist
));
5559 Set_Aggregate_Bounds
(N
, Aggregate_Bounds
(Original_Node
(N
)));
5568 function Is_Flat
(N
: Node_Id
; Dims
: Nat
) return Boolean is
5575 elsif Nkind
(N
) = N_Aggregate
then
5576 if Present
(Component_Associations
(N
)) then
5580 Elmt
:= First
(Expressions
(N
));
5581 while Present
(Elmt
) loop
5582 if not Is_Flat
(Elmt
, Dims
- 1) then
5596 -------------------------
5597 -- Is_Static_Element --
5598 -------------------------
5600 function Is_Static_Element
(N
: Node_Id
; Dims
: Nat
) return Boolean is
5601 Expr
: constant Node_Id
:= Expression
(N
);
5604 -- In most cases the interesting expressions are unambiguously static
5606 if Compile_Time_Known_Value
(Expr
) then
5609 elsif Nkind
(N
) = N_Iterated_Component_Association
then
5612 elsif Nkind
(Expr
) = N_Aggregate
5613 and then Compile_Time_Known_Aggregate
(Expr
)
5614 and then not Expansion_Delayed
(Expr
)
5618 -- However, one may write static expressions that are syntactically
5619 -- ambiguous, so preanalyze the expression before checking it again,
5620 -- but only at the innermost level for a multidimensional array.
5623 Preanalyze_And_Resolve
(Expr
, Component_Type
(Typ
));
5624 return Compile_Time_Known_Value
(Expr
);
5629 end Is_Static_Element
;
5631 -- Start of processing for Convert_To_Positional
5634 -- Only convert to positional when generating C in case of an
5635 -- object declaration, this is the only case where aggregates are
5638 if Modify_Tree_For_C
and then not Is_CCG_Supported_Aggregate
(N
) then
5642 -- Ada 2005 (AI-287): Do not convert in case of default initialized
5643 -- components because in this case will need to call the corresponding
5646 if Has_Default_Init_Comps
(N
) then
5650 -- A subaggregate may have been flattened but is not known to be
5651 -- Compile_Time_Known. Set that flag in cases that cannot require
5652 -- elaboration code, so that the aggregate can be used as the
5653 -- initial value of a thread-local variable.
5655 if Is_Flat
(N
, Dims
) then
5656 if Static_Array_Aggregate
(N
) then
5657 Set_Compile_Time_Known_Aggregate
(N
);
5663 if Is_Bit_Packed_Array
(Typ
) and then not Handle_Bit_Packed
then
5667 -- Do not convert to positional if controlled components are involved
5668 -- since these require special processing
5670 if Has_Controlled_Component
(Typ
) then
5674 Check_Static_Components
;
5676 -- If the size is known, or all the components are static, try to
5677 -- build a fully positional aggregate.
5679 -- The size of the type may not be known for an aggregate with
5680 -- discriminated array components, but if the components are static
5681 -- it is still possible to verify statically that the length is
5682 -- compatible with the upper bound of the type, and therefore it is
5683 -- worth flattening such aggregates as well.
5687 Flatten
(N
, Dims
, First_Index
(Typ
), First_Index
(Base_Type
(Typ
)))
5689 if Static_Components
then
5690 Set_Compile_Time_Known_Aggregate
(N
);
5691 Set_Expansion_Delayed
(N
, False);
5694 Analyze_And_Resolve
(N
, Typ
);
5697 -- If Static_Elaboration_Desired has been specified, diagnose aggregates
5698 -- that will still require initialization code.
5700 if (Ekind
(Current_Scope
) = E_Package
5701 and then Static_Elaboration_Desired
(Current_Scope
))
5702 and then Nkind
(Parent
(N
)) = N_Object_Declaration
5708 if Nkind
(N
) = N_Aggregate
and then Present
(Expressions
(N
)) then
5709 Expr
:= First
(Expressions
(N
));
5710 while Present
(Expr
) loop
5711 if not Compile_Time_Known_Value
(Expr
) then
5713 ("non-static object requires elaboration code??", N
);
5720 if Present
(Component_Associations
(N
)) then
5721 Error_Msg_N
("object requires elaboration code??", N
);
5726 end Convert_To_Positional
;
5728 ----------------------------
5729 -- Expand_Array_Aggregate --
5730 ----------------------------
5732 -- Array aggregate expansion proceeds as follows:
5734 -- 1. If requested we generate code to perform all the array aggregate
5735 -- bound checks, specifically
5737 -- (a) Check that the index range defined by aggregate bounds is
5738 -- compatible with corresponding index subtype.
5740 -- (b) If an others choice is present check that no aggregate
5741 -- index is outside the bounds of the index constraint.
5743 -- (c) For multidimensional arrays make sure that all subaggregates
5744 -- corresponding to the same dimension have the same bounds.
5746 -- 2. Check for packed array aggregate which can be converted to a
5747 -- constant so that the aggregate disappears completely.
5749 -- 3. Check case of nested aggregate. Generally nested aggregates are
5750 -- handled during the processing of the parent aggregate.
5752 -- 4. Check if the aggregate can be statically processed. If this is the
5753 -- case pass it as is to Gigi. Note that a necessary condition for
5754 -- static processing is that the aggregate be fully positional.
5756 -- 5. If in-place aggregate expansion is possible (i.e. no need to create
5757 -- a temporary) then mark the aggregate as such and return. Otherwise
5758 -- create a new temporary and generate the appropriate initialization
5761 procedure Expand_Array_Aggregate
(N
: Node_Id
) is
5762 Loc
: constant Source_Ptr
:= Sloc
(N
);
5764 Typ
: constant Entity_Id
:= Etype
(N
);
5765 Ctyp
: constant Entity_Id
:= Component_Type
(Typ
);
5766 -- Typ is the correct constrained array subtype of the aggregate
5767 -- Ctyp is the corresponding component type.
5769 Aggr_Dimension
: constant Pos
:= Number_Dimensions
(Typ
);
5770 -- Number of aggregate index dimensions
5772 Aggr_Low
: array (1 .. Aggr_Dimension
) of Node_Id
;
5773 Aggr_High
: array (1 .. Aggr_Dimension
) of Node_Id
;
5774 -- Low and High bounds of the constraint for each aggregate index
5776 Aggr_Index_Typ
: array (1 .. Aggr_Dimension
) of Entity_Id
;
5777 -- The type of each index
5779 In_Place_Assign_OK_For_Declaration
: Boolean := False;
5780 -- True if we are to generate an in-place assignment for a declaration
5782 Maybe_In_Place_OK
: Boolean;
5783 -- If the type is neither controlled nor packed and the aggregate
5784 -- is the expression in an assignment, assignment in place may be
5785 -- possible, provided other conditions are met on the LHS.
5787 Others_Present
: array (1 .. Aggr_Dimension
) of Boolean :=
5789 -- If Others_Present (J) is True, then there is an others choice in one
5790 -- of the subaggregates of N at dimension J.
5792 procedure Build_Constrained_Type
(Positional
: Boolean);
5793 -- If the subtype is not static or unconstrained, build a constrained
5794 -- type using the computable sizes of the aggregate and its sub-
5797 procedure Check_Bounds
(Aggr_Bounds_Node
, Index_Bounds_Node
: Node_Id
);
5798 -- Checks that the bounds of Aggr_Bounds are within the bounds defined
5799 -- by Index_Bounds. For null array aggregate (Ada 2022) check that the
5800 -- aggregate bounds define a null range.
5802 procedure Check_Same_Aggr_Bounds
(Sub_Aggr
: Node_Id
; Dim
: Pos
);
5803 -- Checks that in a multidimensional array aggregate all subaggregates
5804 -- corresponding to the same dimension have the same bounds. Sub_Aggr is
5805 -- an array subaggregate. Dim is the dimension corresponding to the
5808 procedure Compute_Others_Present
(Sub_Aggr
: Node_Id
; Dim
: Pos
);
5809 -- Computes the values of array Others_Present. Sub_Aggr is the array
5810 -- subaggregate we start the computation from. Dim is the dimension
5811 -- corresponding to the subaggregate.
5813 procedure Others_Check
(Sub_Aggr
: Node_Id
; Dim
: Pos
);
5814 -- Checks that if an others choice is present in any subaggregate, no
5815 -- aggregate index is outside the bounds of the index constraint.
5816 -- Sub_Aggr is an array subaggregate. Dim is the dimension corresponding
5817 -- to the subaggregate.
5819 function Safe_Left_Hand_Side
(N
: Node_Id
) return Boolean;
5820 -- In addition to Maybe_In_Place_OK, in order for an aggregate to be
5821 -- built directly into the target of the assignment it must be free
5822 -- of side effects. N is the LHS of an assignment.
5824 procedure Two_Pass_Aggregate_Expansion
(N
: Node_Id
);
5825 -- If the aggregate consists only of iterated associations then the
5826 -- aggregate is constructed in two steps:
5827 -- a) Build an expression to compute the number of elements
5828 -- generated by each iterator, and use the expression to allocate
5829 -- the destination aggregate.
5830 -- b) Generate the loops corresponding to each iterator to insert
5831 -- the elements in their proper positions.
5833 ----------------------------
5834 -- Build_Constrained_Type --
5835 ----------------------------
5837 procedure Build_Constrained_Type
(Positional
: Boolean) is
5838 Loc
: constant Source_Ptr
:= Sloc
(N
);
5839 Agg_Type
: constant Entity_Id
:= Make_Temporary
(Loc
, 'A');
5842 Typ
: constant Entity_Id
:= Etype
(N
);
5843 Indexes
: constant List_Id
:= New_List
;
5848 -- If the aggregate is purely positional, all its subaggregates
5849 -- have the same size. We collect the dimensions from the first
5850 -- subaggregate at each level.
5855 for D
in 1 .. Number_Dimensions
(Typ
) loop
5856 Sub_Agg
:= First
(Expressions
(Sub_Agg
));
5860 while Present
(Comp
) loop
5867 Low_Bound
=> Make_Integer_Literal
(Loc
, 1),
5868 High_Bound
=> Make_Integer_Literal
(Loc
, Num
)));
5872 -- We know the aggregate type is unconstrained and the aggregate
5873 -- is not processable by the back end, therefore not necessarily
5874 -- positional. Retrieve each dimension bounds (computed earlier).
5876 for D
in 1 .. Number_Dimensions
(Typ
) loop
5879 Low_Bound
=> Aggr_Low
(D
),
5880 High_Bound
=> Aggr_High
(D
)));
5885 Make_Full_Type_Declaration
(Loc
,
5886 Defining_Identifier
=> Agg_Type
,
5888 Make_Constrained_Array_Definition
(Loc
,
5889 Discrete_Subtype_Definitions
=> Indexes
,
5890 Component_Definition
=>
5891 Make_Component_Definition
(Loc
,
5892 Aliased_Present
=> False,
5893 Subtype_Indication
=>
5894 New_Occurrence_Of
(Component_Type
(Typ
), Loc
))));
5896 Insert_Action
(N
, Decl
);
5898 Set_Etype
(N
, Agg_Type
);
5899 Set_Is_Itype
(Agg_Type
);
5900 Freeze_Itype
(Agg_Type
, N
);
5901 end Build_Constrained_Type
;
5907 procedure Check_Bounds
(Aggr_Bounds_Node
, Index_Bounds_Node
: Node_Id
) is
5908 Aggr_Bounds
: constant Range_Nodes
:=
5909 Get_Index_Bounds
(Aggr_Bounds_Node
);
5910 Ind_Bounds
: constant Range_Nodes
:=
5911 Get_Index_Bounds
(Index_Bounds_Node
);
5913 Cond
: Node_Id
:= Empty
;
5916 -- For a null array aggregate check that high bound (i.e., low
5917 -- bound predecessor) exists. Fail if low bound is low bound of
5918 -- base subtype (in all cases, including modular).
5920 if Is_Null_Aggregate
(N
) then
5922 Make_Raise_Constraint_Error
(Loc
,
5925 New_Copy_Tree
(Aggr_Bounds
.First
),
5927 (Type_Low_Bound
(Base_Type
(Etype
(Ind_Bounds
.First
))))),
5928 Reason
=> CE_Range_Check_Failed
));
5932 -- Generate the following test:
5934 -- [constraint_error when
5935 -- Aggr_Bounds.First <= Aggr_Bounds.Last and then
5936 -- (Aggr_Bounds.First < Ind_Bounds.First
5937 -- or else Aggr_Bounds.Last > Ind_Bounds.Last)]
5939 -- As an optimization try to see if some tests are trivially vacuous
5940 -- because we are comparing an expression against itself.
5942 if Aggr_Bounds
.First
= Ind_Bounds
.First
5943 and then Aggr_Bounds
.Last
= Ind_Bounds
.Last
5947 elsif Aggr_Bounds
.Last
= Ind_Bounds
.Last
then
5951 Duplicate_Subexpr_Move_Checks
(Aggr_Bounds
.First
),
5953 Duplicate_Subexpr_Move_Checks
(Ind_Bounds
.First
));
5955 elsif Aggr_Bounds
.First
= Ind_Bounds
.First
then
5958 Left_Opnd
=> Duplicate_Subexpr_Move_Checks
(Aggr_Bounds
.Last
),
5959 Right_Opnd
=> Duplicate_Subexpr_Move_Checks
(Ind_Bounds
.Last
));
5967 Duplicate_Subexpr_Move_Checks
(Aggr_Bounds
.First
),
5969 Duplicate_Subexpr_Move_Checks
(Ind_Bounds
.First
)),
5973 Left_Opnd
=> Duplicate_Subexpr
(Aggr_Bounds
.Last
),
5974 Right_Opnd
=> Duplicate_Subexpr
(Ind_Bounds
.Last
)));
5977 if Present
(Cond
) then
5983 Duplicate_Subexpr_Move_Checks
(Aggr_Bounds
.First
),
5985 Duplicate_Subexpr_Move_Checks
(Aggr_Bounds
.Last
)),
5987 Right_Opnd
=> Cond
);
5989 Set_Analyzed
(Left_Opnd
(Left_Opnd
(Cond
)), False);
5990 Set_Analyzed
(Right_Opnd
(Left_Opnd
(Cond
)), False);
5992 Make_Raise_Constraint_Error
(Loc
,
5994 Reason
=> CE_Range_Check_Failed
));
5998 ----------------------------
5999 -- Check_Same_Aggr_Bounds --
6000 ----------------------------
6002 procedure Check_Same_Aggr_Bounds
(Sub_Aggr
: Node_Id
; Dim
: Pos
) is
6003 Sub_Bounds
: constant Range_Nodes
6004 := Get_Index_Bounds
(Aggregate_Bounds
(Sub_Aggr
));
6005 Sub_Lo
: Node_Id
renames Sub_Bounds
.First
;
6006 Sub_Hi
: Node_Id
renames Sub_Bounds
.Last
;
6007 -- The bounds of this specific subaggregate
6009 Aggr_Lo
: constant Node_Id
:= Aggr_Low
(Dim
);
6010 Aggr_Hi
: constant Node_Id
:= Aggr_High
(Dim
);
6011 -- The bounds of the aggregate for this dimension
6013 Ind_Typ
: constant Entity_Id
:= Aggr_Index_Typ
(Dim
);
6014 -- The index type for this dimension.xxx
6016 Cond
: Node_Id
:= Empty
;
6021 -- If index checks are on generate the test
6023 -- [constraint_error when
6024 -- Aggr_Lo /= Sub_Lo or else Aggr_Hi /= Sub_Hi]
6026 -- As an optimization try to see if some tests are trivially vacuos
6027 -- because we are comparing an expression against itself. Also for
6028 -- the first dimension the test is trivially vacuous because there
6029 -- is just one aggregate for dimension 1.
6031 if Index_Checks_Suppressed
(Ind_Typ
) then
6034 elsif Dim
= 1 or else (Aggr_Lo
= Sub_Lo
and then Aggr_Hi
= Sub_Hi
)
6038 elsif Aggr_Hi
= Sub_Hi
then
6041 Left_Opnd
=> Duplicate_Subexpr_Move_Checks
(Aggr_Lo
),
6042 Right_Opnd
=> Duplicate_Subexpr_Move_Checks
(Sub_Lo
));
6044 elsif Aggr_Lo
= Sub_Lo
then
6047 Left_Opnd
=> Duplicate_Subexpr_Move_Checks
(Aggr_Hi
),
6048 Right_Opnd
=> Duplicate_Subexpr_Move_Checks
(Sub_Hi
));
6055 Left_Opnd
=> Duplicate_Subexpr_Move_Checks
(Aggr_Lo
),
6056 Right_Opnd
=> Duplicate_Subexpr_Move_Checks
(Sub_Lo
)),
6060 Left_Opnd
=> Duplicate_Subexpr
(Aggr_Hi
),
6061 Right_Opnd
=> Duplicate_Subexpr
(Sub_Hi
)));
6064 if Present
(Cond
) then
6066 Make_Raise_Constraint_Error
(Loc
,
6068 Reason
=> CE_Length_Check_Failed
));
6071 -- Now look inside the subaggregate to see if there is more work
6073 if Dim
< Aggr_Dimension
then
6075 -- Process positional components
6077 if Present
(Expressions
(Sub_Aggr
)) then
6078 Expr
:= First
(Expressions
(Sub_Aggr
));
6079 while Present
(Expr
) loop
6080 Check_Same_Aggr_Bounds
(Expr
, Dim
+ 1);
6085 -- Process component associations
6087 if Present
(Component_Associations
(Sub_Aggr
)) then
6088 Assoc
:= First
(Component_Associations
(Sub_Aggr
));
6089 while Present
(Assoc
) loop
6090 Expr
:= Expression
(Assoc
);
6091 Check_Same_Aggr_Bounds
(Expr
, Dim
+ 1);
6096 end Check_Same_Aggr_Bounds
;
6098 ----------------------------
6099 -- Compute_Others_Present --
6100 ----------------------------
6102 procedure Compute_Others_Present
(Sub_Aggr
: Node_Id
; Dim
: Pos
) is
6107 if Present
(Component_Associations
(Sub_Aggr
)) then
6108 Assoc
:= Last
(Component_Associations
(Sub_Aggr
));
6111 and then Nkind
(First
(Choice_List
(Assoc
))) = N_Others_Choice
6113 Others_Present
(Dim
) := True;
6115 -- An others_clause may be superfluous if previous components
6116 -- cover the full given range of a constrained array. In such
6117 -- a case an others_clause does not contribute any additional
6118 -- components and has not been analyzed. We analyze it now to
6119 -- detect type errors in the expression, even though no code
6120 -- will be generated for it.
6122 if Dim
= Aggr_Dimension
6123 and then Nkind
(Assoc
) /= N_Iterated_Component_Association
6124 and then not Analyzed
(Expression
(Assoc
))
6125 and then not Box_Present
(Assoc
)
6127 Preanalyze_And_Resolve
(Expression
(Assoc
), Ctyp
);
6132 -- Now look inside the subaggregate to see if there is more work
6134 if Dim
< Aggr_Dimension
then
6136 -- Process positional components
6138 if Present
(Expressions
(Sub_Aggr
)) then
6139 Expr
:= First
(Expressions
(Sub_Aggr
));
6140 while Present
(Expr
) loop
6141 Compute_Others_Present
(Expr
, Dim
+ 1);
6146 -- Process component associations
6148 if Present
(Component_Associations
(Sub_Aggr
)) then
6149 Assoc
:= First
(Component_Associations
(Sub_Aggr
));
6150 while Present
(Assoc
) loop
6151 Expr
:= Expression
(Assoc
);
6152 Compute_Others_Present
(Expr
, Dim
+ 1);
6157 end Compute_Others_Present
;
6163 procedure Others_Check
(Sub_Aggr
: Node_Id
; Dim
: Pos
) is
6164 Aggr_Lo
: constant Node_Id
:= Aggr_Low
(Dim
);
6165 Aggr_Hi
: constant Node_Id
:= Aggr_High
(Dim
);
6166 -- The bounds of the aggregate for this dimension
6168 Ind_Typ
: constant Entity_Id
:= Aggr_Index_Typ
(Dim
);
6169 -- The index type for this dimension
6171 Need_To_Check
: Boolean := False;
6173 Choices_Lo
: Node_Id
:= Empty
;
6174 Choices_Hi
: Node_Id
:= Empty
;
6175 -- The lowest and highest discrete choices for a named subaggregate
6177 Nb_Choices
: Int
:= -1;
6178 -- The number of discrete non-others choices in this subaggregate
6180 Nb_Elements
: Uint
:= Uint_0
;
6181 -- The number of elements in a positional aggregate
6183 Cond
: Node_Id
:= Empty
;
6190 -- Check if we have an others choice. If we do make sure that this
6191 -- subaggregate contains at least one element in addition to the
6194 if Range_Checks_Suppressed
(Ind_Typ
) then
6195 Need_To_Check
:= False;
6197 elsif Present
(Expressions
(Sub_Aggr
))
6198 and then Present
(Component_Associations
(Sub_Aggr
))
6201 not (Is_Empty_List
(Expressions
(Sub_Aggr
))
6202 and then Is_Empty_List
6203 (Component_Associations
(Sub_Aggr
)));
6205 elsif Present
(Component_Associations
(Sub_Aggr
)) then
6206 Assoc
:= Last
(Component_Associations
(Sub_Aggr
));
6208 if Nkind
(First
(Choice_List
(Assoc
))) /= N_Others_Choice
then
6209 Need_To_Check
:= False;
6212 -- Count the number of discrete choices. Start with -1 because
6213 -- the others choice does not count.
6215 -- Is there some reason we do not use List_Length here ???
6218 Assoc
:= First
(Component_Associations
(Sub_Aggr
));
6219 while Present
(Assoc
) loop
6220 Choice
:= First
(Choice_List
(Assoc
));
6221 while Present
(Choice
) loop
6222 Nb_Choices
:= Nb_Choices
+ 1;
6229 -- If there is only an others choice nothing to do
6231 Need_To_Check
:= (Nb_Choices
> 0);
6235 Need_To_Check
:= False;
6238 -- If we are dealing with a positional subaggregate with an others
6239 -- choice then compute the number or positional elements.
6241 if Need_To_Check
and then Present
(Expressions
(Sub_Aggr
)) then
6242 Expr
:= First
(Expressions
(Sub_Aggr
));
6243 Nb_Elements
:= Uint_0
;
6244 while Present
(Expr
) loop
6245 Nb_Elements
:= Nb_Elements
+ 1;
6249 -- If the aggregate contains discrete choices and an others choice
6250 -- compute the smallest and largest discrete choice values.
6252 elsif Need_To_Check
then
6253 Compute_Choices_Lo_And_Choices_Hi
: declare
6255 Table
: Case_Table_Type
(1 .. Nb_Choices
);
6256 -- Used to sort all the different choice values
6261 Assoc
:= First
(Component_Associations
(Sub_Aggr
));
6262 while Present
(Assoc
) loop
6263 Choice
:= First
(Choice_List
(Assoc
));
6264 while Present
(Choice
) loop
6265 if Nkind
(Choice
) = N_Others_Choice
then
6270 Bounds
: constant Range_Nodes
:=
6271 Get_Index_Bounds
(Choice
);
6273 Table
(J
).Choice_Lo
:= Bounds
.First
;
6274 Table
(J
).Choice_Hi
:= Bounds
.Last
;
6284 -- Sort the discrete choices
6286 Sort_Case_Table
(Table
);
6288 Choices_Lo
:= Table
(1).Choice_Lo
;
6289 Choices_Hi
:= Table
(Nb_Choices
).Choice_Hi
;
6290 end Compute_Choices_Lo_And_Choices_Hi
;
6293 -- If no others choice in this subaggregate, or the aggregate
6294 -- comprises only an others choice, nothing to do.
6296 if not Need_To_Check
then
6299 -- If we are dealing with an aggregate containing an others choice
6300 -- and positional components, we generate the following test:
6302 -- if Ind_Typ'Pos (Aggr_Lo) + (Nb_Elements - 1) >
6303 -- Ind_Typ'Pos (Aggr_Hi)
6305 -- raise Constraint_Error;
6308 -- in the general case, but the following simpler test:
6310 -- [constraint_error when
6311 -- Aggr_Lo + (Nb_Elements - 1) > Aggr_Hi];
6313 -- instead if the index type is a signed integer.
6315 elsif Nb_Elements
> Uint_0
then
6316 if Nb_Elements
= Uint_1
then
6319 Left_Opnd
=> Duplicate_Subexpr_Move_Checks
(Aggr_Lo
),
6320 Right_Opnd
=> Duplicate_Subexpr_Move_Checks
(Aggr_Hi
));
6322 elsif Is_Signed_Integer_Type
(Ind_Typ
) then
6327 Left_Opnd
=> Duplicate_Subexpr_Move_Checks
(Aggr_Lo
),
6329 Make_Integer_Literal
(Loc
, Nb_Elements
- 1)),
6330 Right_Opnd
=> Duplicate_Subexpr_Move_Checks
(Aggr_Hi
));
6338 Make_Attribute_Reference
(Loc
,
6339 Prefix
=> New_Occurrence_Of
(Ind_Typ
, Loc
),
6340 Attribute_Name
=> Name_Pos
,
6343 (Duplicate_Subexpr_Move_Checks
(Aggr_Lo
))),
6344 Right_Opnd
=> Make_Integer_Literal
(Loc
, Nb_Elements
- 1)),
6347 Make_Attribute_Reference
(Loc
,
6348 Prefix
=> New_Occurrence_Of
(Ind_Typ
, Loc
),
6349 Attribute_Name
=> Name_Pos
,
6350 Expressions
=> New_List
(
6351 Duplicate_Subexpr_Move_Checks
(Aggr_Hi
))));
6354 -- If we are dealing with an aggregate containing an others choice
6355 -- and discrete choices we generate the following test:
6357 -- [constraint_error when
6358 -- Choices_Lo < Aggr_Lo or else Choices_Hi > Aggr_Hi];
6365 Left_Opnd
=> Duplicate_Subexpr_Move_Checks
(Choices_Lo
),
6366 Right_Opnd
=> Duplicate_Subexpr_Move_Checks
(Aggr_Lo
)),
6370 Left_Opnd
=> Duplicate_Subexpr
(Choices_Hi
),
6371 Right_Opnd
=> Duplicate_Subexpr
(Aggr_Hi
)));
6374 if Present
(Cond
) then
6376 Make_Raise_Constraint_Error
(Loc
,
6378 Reason
=> CE_Length_Check_Failed
));
6379 -- Questionable reason code, shouldn't that be a
6380 -- CE_Range_Check_Failed ???
6383 -- Now look inside the subaggregate to see if there is more work
6385 if Dim
< Aggr_Dimension
then
6387 -- Process positional components
6389 if Present
(Expressions
(Sub_Aggr
)) then
6390 Expr
:= First
(Expressions
(Sub_Aggr
));
6391 while Present
(Expr
) loop
6392 Others_Check
(Expr
, Dim
+ 1);
6397 -- Process component associations
6399 if Present
(Component_Associations
(Sub_Aggr
)) then
6400 Assoc
:= First
(Component_Associations
(Sub_Aggr
));
6401 while Present
(Assoc
) loop
6402 Expr
:= Expression
(Assoc
);
6403 Others_Check
(Expr
, Dim
+ 1);
6410 -------------------------
6411 -- Safe_Left_Hand_Side --
6412 -------------------------
6414 function Safe_Left_Hand_Side
(N
: Node_Id
) return Boolean is
6415 function Is_Safe_Index
(Indx
: Node_Id
) return Boolean;
6416 -- If the left-hand side includes an indexed component, check that
6417 -- the indexes are free of side effects.
6423 function Is_Safe_Index
(Indx
: Node_Id
) return Boolean is
6425 if Is_Entity_Name
(Indx
) then
6428 elsif Nkind
(Indx
) = N_Integer_Literal
then
6431 elsif Nkind
(Indx
) = N_Function_Call
6432 and then Is_Entity_Name
(Name
(Indx
))
6433 and then Has_Pragma_Pure_Function
(Entity
(Name
(Indx
)))
6437 elsif Nkind
(Indx
) = N_Type_Conversion
6438 and then Is_Safe_Index
(Expression
(Indx
))
6447 -- Start of processing for Safe_Left_Hand_Side
6450 if Is_Entity_Name
(N
) then
6453 elsif Nkind
(N
) in N_Explicit_Dereference | N_Selected_Component
6454 and then Safe_Left_Hand_Side
(Prefix
(N
))
6458 elsif Nkind
(N
) = N_Indexed_Component
6459 and then Safe_Left_Hand_Side
(Prefix
(N
))
6460 and then Is_Safe_Index
(First
(Expressions
(N
)))
6464 elsif Nkind
(N
) = N_Unchecked_Type_Conversion
then
6465 return Safe_Left_Hand_Side
(Expression
(N
));
6470 end Safe_Left_Hand_Side
;
6472 ----------------------------------
6473 -- Two_Pass_Aggregate_Expansion --
6474 ----------------------------------
6476 procedure Two_Pass_Aggregate_Expansion
(N
: Node_Id
) is
6477 Loc
: constant Source_Ptr
:= Sloc
(N
);
6478 Comp_Type
: constant Entity_Id
:= Etype
(N
);
6479 Index_Id
: constant Entity_Id
:= Make_Temporary
(Loc
, 'I', N
);
6480 Index_Type
: constant Entity_Id
:= Etype
(First_Index
(Etype
(N
)));
6481 Size_Id
: constant Entity_Id
:= Make_Temporary
(Loc
, 'I', N
);
6482 TmpE
: constant Entity_Id
:= Make_Temporary
(Loc
, 'A', N
);
6484 Assoc
: Node_Id
:= First
(Component_Associations
(N
));
6490 Size_Expr_Code
: List_Id
;
6491 Insertion_Code
: List_Id
:= New_List
;
6494 Size_Expr_Code
:= New_List
(
6495 Make_Object_Declaration
(Loc
,
6496 Defining_Identifier
=> Size_Id
,
6497 Object_Definition
=> New_Occurrence_Of
(Standard_Integer
, Loc
),
6498 Expression
=> Make_Integer_Literal
(Loc
, 0)));
6500 -- First pass: execute the iterators to count the number of elements
6501 -- that will be generated.
6503 while Present
(Assoc
) loop
6504 Iter
:= Iterator_Specification
(Assoc
);
6505 Incr
:= Make_Assignment_Statement
(Loc
,
6506 Name
=> New_Occurrence_Of
(Size_Id
, Loc
),
6509 Left_Opnd
=> New_Occurrence_Of
(Size_Id
, Loc
),
6510 Right_Opnd
=> Make_Integer_Literal
(Loc
, 1)));
6512 One_Loop
:= Make_Implicit_Loop_Statement
(N
,
6514 Make_Iteration_Scheme
(Loc
,
6515 Iterator_Specification
=> New_Copy_Tree
(Iter
)),
6516 Statements
=> New_List
(Incr
));
6518 Append
(One_Loop
, Size_Expr_Code
);
6522 Insert_Actions
(N
, Size_Expr_Code
);
6524 -- Build a constrained subtype with the calculated length
6525 -- and declare the proper bounded aggregate object.
6526 -- The index type is some discrete type, so the bounds of the
6527 -- constructed array are computed as T'Val (T'Pos (ineger bound));
6530 Pos_Lo
: constant Node_Id
:=
6531 Make_Attribute_Reference
(Loc
,
6532 Prefix
=> New_Occurrence_Of
(Index_Type
, Loc
),
6533 Attribute_Name
=> Name_Pos
,
6534 Expressions
=> New_List
(
6535 Make_Attribute_Reference
(Loc
,
6536 Prefix
=> New_Occurrence_Of
(Index_Type
, Loc
),
6537 Attribute_Name
=> Name_First
)));
6539 Aggr_Lo
: constant Node_Id
:=
6540 Make_Attribute_Reference
(Loc
,
6541 Prefix
=> New_Occurrence_Of
(Index_Type
, Loc
),
6542 Attribute_Name
=> Name_Val
,
6543 Expressions
=> New_List
(New_Copy_Tree
(Pos_Lo
)));
6545 -- Hi = Index_type'Pos (Lo + Size -1).
6547 Pos_Hi
: constant Node_Id
:=
6549 Left_Opnd
=> New_Copy_Tree
(Pos_Lo
),
6551 Make_Op_Subtract
(Loc
,
6552 Left_Opnd
=> New_Occurrence_Of
(Size_Id
, Loc
),
6553 Right_Opnd
=> Make_Integer_Literal
(Loc
, 1)));
6555 -- Corresponding index value
6557 Aggr_Hi
: constant Node_Id
:=
6558 Make_Attribute_Reference
(Loc
,
6559 Prefix
=> New_Occurrence_Of
(Index_Type
, Loc
),
6560 Attribute_Name
=> Name_Val
,
6561 Expressions
=> New_List
(New_Copy_Tree
(Pos_Hi
)));
6563 SubE
: constant Entity_Id
:= Make_Temporary
(Loc
, 'T');
6564 SubD
: constant Node_Id
:=
6565 Make_Subtype_Declaration
(Loc
,
6566 Defining_Identifier
=> SubE
,
6567 Subtype_Indication
=>
6568 Make_Subtype_Indication
(Loc
,
6570 New_Occurrence_Of
(Etype
(Comp_Type
), Loc
),
6572 Make_Index_Or_Discriminant_Constraint
6575 New_List
(Make_Range
(Loc
, Aggr_Lo
, Aggr_Hi
)))));
6577 -- Create a temporary array of the above subtype which
6578 -- will be used to capture the aggregate assignments.
6580 TmpD
: constant Node_Id
:=
6581 Make_Object_Declaration
(Loc
,
6582 Defining_Identifier
=> TmpE
,
6583 Object_Definition
=> New_Occurrence_Of
(SubE
, Loc
));
6585 Insert_Actions
(N
, New_List
(SubD
, TmpD
));
6588 -- Second pass: use the iterators to generate the elements of the
6589 -- aggregate. Insertion index starts at Index_Type'First. We
6590 -- assume that the second evaluation of each iterator generates
6591 -- the same number of elements as the first pass, and consider
6592 -- that the execution is erroneous (even if the RM does not state
6593 -- this explicitly) if the number of elements generated differs
6594 -- between first and second pass.
6596 Assoc
:= First
(Component_Associations
(N
));
6598 -- Initialize insertion position to first array component.
6600 Insertion_Code
:= New_List
(
6601 Make_Object_Declaration
(Loc
,
6602 Defining_Identifier
=> Index_Id
,
6603 Object_Definition
=>
6604 New_Occurrence_Of
(Index_Type
, Loc
),
6606 Make_Attribute_Reference
(Loc
,
6607 Prefix
=> New_Occurrence_Of
(Index_Type
, Loc
),
6608 Attribute_Name
=> Name_First
)));
6610 while Present
(Assoc
) loop
6611 Iter
:= Iterator_Specification
(Assoc
);
6612 New_Comp
:= Make_Assignment_Statement
(Loc
,
6614 Make_Indexed_Component
(Loc
,
6615 Prefix
=> New_Occurrence_Of
(TmpE
, Loc
),
6617 New_List
(New_Occurrence_Of
(Index_Id
, Loc
))),
6618 Expression
=> Copy_Separate_Tree
(Expression
(Assoc
)));
6620 -- Advance index position for insertion.
6622 Incr
:= Make_Assignment_Statement
(Loc
,
6623 Name
=> New_Occurrence_Of
(Index_Id
, Loc
),
6625 Make_Attribute_Reference
(Loc
,
6627 New_Occurrence_Of
(Index_Type
, Loc
),
6628 Attribute_Name
=> Name_Succ
,
6630 New_List
(New_Occurrence_Of
(Index_Id
, Loc
))));
6632 -- Add guard to skip last increment when upper bound is reached.
6634 Incr
:= Make_If_Statement
(Loc
,
6637 Left_Opnd
=> New_Occurrence_Of
(Index_Id
, Loc
),
6639 Make_Attribute_Reference
(Loc
,
6640 Prefix
=> New_Occurrence_Of
(Index_Type
, Loc
),
6641 Attribute_Name
=> Name_Last
)),
6642 Then_Statements
=> New_List
(Incr
));
6644 One_Loop
:= Make_Implicit_Loop_Statement
(N
,
6646 Make_Iteration_Scheme
(Loc
,
6647 Iterator_Specification
=> Copy_Separate_Tree
(Iter
)),
6648 Statements
=> New_List
(New_Comp
, Incr
));
6650 Append
(One_Loop
, Insertion_Code
);
6654 Insert_Actions
(N
, Insertion_Code
);
6656 -- Depending on context this may not work for build-in-place
6659 Rewrite
(N
, New_Occurrence_Of
(TmpE
, Loc
));
6661 end Two_Pass_Aggregate_Expansion
;
6666 -- Holds the temporary aggregate value
6669 -- Holds the declaration of Tmp
6671 Aggr_Code
: List_Id
;
6672 Parent_Node
: Node_Id
;
6673 Parent_Kind
: Node_Kind
;
6675 -- Start of processing for Expand_Array_Aggregate
6678 -- Do not touch the special aggregates of attributes used for Asm calls
6680 if Is_RTE
(Ctyp
, RE_Asm_Input_Operand
)
6681 or else Is_RTE
(Ctyp
, RE_Asm_Output_Operand
)
6685 elsif Present
(Component_Associations
(N
))
6686 and then Nkind
(First
(Component_Associations
(N
))) =
6687 N_Iterated_Component_Association
6689 Present
(Iterator_Specification
(First
(Component_Associations
(N
))))
6691 Two_Pass_Aggregate_Expansion
(N
);
6694 -- Do not attempt expansion if error already detected. We may reach this
6695 -- point in spite of previous errors when compiling with -gnatq, to
6696 -- force all possible errors (this is the usual ACATS mode).
6698 elsif Error_Posted
(N
) then
6702 -- If the semantic analyzer has determined that aggregate N will raise
6703 -- Constraint_Error at run time, then the aggregate node has been
6704 -- replaced with an N_Raise_Constraint_Error node and we should
6707 pragma Assert
(not Raises_Constraint_Error
(N
));
6711 -- Check that the index range defined by aggregate bounds is
6712 -- compatible with corresponding index subtype.
6714 Index_Compatibility_Check
: declare
6715 Aggr_Index_Range
: Node_Id
:= First_Index
(Typ
);
6716 -- The current aggregate index range
6718 Index_Constraint
: Node_Id
:= First_Index
(Etype
(Typ
));
6719 -- The corresponding index constraint against which we have to
6720 -- check the above aggregate index range.
6723 Compute_Others_Present
(N
, 1);
6725 for J
in 1 .. Aggr_Dimension
loop
6726 -- There is no need to emit a check if an others choice is present
6727 -- for this array aggregate dimension since in this case one of
6728 -- N's subaggregates has taken its bounds from the context and
6729 -- these bounds must have been checked already. In addition all
6730 -- subaggregates corresponding to the same dimension must all have
6731 -- the same bounds (checked in (c) below).
6733 if not Range_Checks_Suppressed
(Etype
(Index_Constraint
))
6734 and then not Others_Present
(J
)
6736 -- We don't use Checks.Apply_Range_Check here because it emits
6737 -- a spurious check. Namely it checks that the range defined by
6738 -- the aggregate bounds is nonempty. But we know this already
6741 Check_Bounds
(Aggr_Index_Range
, Index_Constraint
);
6744 -- Save the low and high bounds of the aggregate index as well as
6745 -- the index type for later use in checks (b) and (c) below.
6748 (Aggr_Index_Range
, L
=> Aggr_Low
(J
), H
=> Aggr_High
(J
));
6750 Aggr_Index_Typ
(J
) := Etype
(Index_Constraint
);
6752 Next_Index
(Aggr_Index_Range
);
6753 Next_Index
(Index_Constraint
);
6755 end Index_Compatibility_Check
;
6759 -- If an others choice is present check that no aggregate index is
6760 -- outside the bounds of the index constraint.
6762 Others_Check
(N
, 1);
6766 -- For multidimensional arrays make sure that all subaggregates
6767 -- corresponding to the same dimension have the same bounds.
6769 if Aggr_Dimension
> 1 then
6770 Check_Same_Aggr_Bounds
(N
, 1);
6775 -- If we have a default component value, or simple initialization is
6776 -- required for the component type, then we replace <> in component
6777 -- associations by the required default value.
6780 Default_Val
: Node_Id
;
6784 if (Present
(Default_Aspect_Component_Value
(Typ
))
6785 or else Needs_Simple_Initialization
(Ctyp
))
6786 and then Present
(Component_Associations
(N
))
6788 Assoc
:= First
(Component_Associations
(N
));
6789 while Present
(Assoc
) loop
6790 if Nkind
(Assoc
) = N_Component_Association
6791 and then Box_Present
(Assoc
)
6793 Set_Box_Present
(Assoc
, False);
6795 if Present
(Default_Aspect_Component_Value
(Typ
)) then
6796 Default_Val
:= Default_Aspect_Component_Value
(Typ
);
6798 Default_Val
:= Get_Simple_Init_Val
(Ctyp
, N
);
6801 Set_Expression
(Assoc
, New_Copy_Tree
(Default_Val
));
6802 Analyze_And_Resolve
(Expression
(Assoc
), Ctyp
);
6812 -- Here we test for is packed array aggregate that we can handle at
6813 -- compile time. If so, return with transformation done. Note that we do
6814 -- this even if the aggregate is nested, because once we have done this
6815 -- processing, there is no more nested aggregate.
6817 if Packed_Array_Aggregate_Handled
(N
) then
6821 -- At this point we try to convert to positional form
6823 Convert_To_Positional
(N
);
6825 -- If the result is no longer an aggregate (e.g. it may be a string
6826 -- literal, or a temporary which has the needed value), then we are
6827 -- done, since there is no longer a nested aggregate.
6829 if Nkind
(N
) /= N_Aggregate
then
6832 -- We are also done if the result is an analyzed aggregate, indicating
6833 -- that Convert_To_Positional succeeded and reanalyzed the rewritten
6836 elsif Analyzed
(N
) and then Is_Rewrite_Substitution
(N
) then
6840 -- If all aggregate components are compile-time known and the aggregate
6841 -- has been flattened, nothing left to do. The same occurs if the
6842 -- aggregate is used to initialize the components of a statically
6843 -- allocated dispatch table.
6845 if Compile_Time_Known_Aggregate
(N
)
6846 or else Is_Static_Dispatch_Table_Aggregate
(N
)
6848 Set_Expansion_Delayed
(N
, False);
6852 -- Now see if back end processing is possible
6854 if Backend_Processing_Possible
(N
) then
6856 -- If the aggregate is static but the constraints are not, build
6857 -- a static subtype for the aggregate, so that Gigi can place it
6858 -- in static memory. Perform an unchecked_conversion to the non-
6859 -- static type imposed by the context.
6862 Itype
: constant Entity_Id
:= Etype
(N
);
6864 Needs_Type
: Boolean := False;
6867 Index
:= First_Index
(Itype
);
6868 while Present
(Index
) loop
6869 if not Is_OK_Static_Subtype
(Etype
(Index
)) then
6878 Build_Constrained_Type
(Positional
=> True);
6879 Rewrite
(N
, Unchecked_Convert_To
(Itype
, N
));
6889 -- Delay expansion for nested aggregates: it will be taken care of when
6890 -- the parent aggregate is expanded.
6892 Parent_Node
:= Parent
(N
);
6893 Parent_Kind
:= Nkind
(Parent_Node
);
6895 if Parent_Kind
= N_Qualified_Expression
then
6896 Parent_Node
:= Parent
(Parent_Node
);
6897 Parent_Kind
:= Nkind
(Parent_Node
);
6900 if Parent_Kind
= N_Aggregate
6901 or else Parent_Kind
= N_Extension_Aggregate
6902 or else Parent_Kind
= N_Component_Association
6903 or else (Parent_Kind
= N_Object_Declaration
6904 and then (Needs_Finalization
(Typ
)
6905 or else Is_Special_Return_Object
6906 (Defining_Identifier
(Parent_Node
))))
6907 or else (Parent_Kind
= N_Assignment_Statement
6908 and then Inside_Init_Proc
)
6910 Set_Expansion_Delayed
(N
, not Static_Array_Aggregate
(N
));
6916 -- Check whether in-place aggregate expansion is possible
6918 -- For object declarations we build the aggregate in place, unless
6919 -- the array is bit-packed.
6921 -- For assignments we do the assignment in place if all the component
6922 -- associations have compile-time known values, or are default-
6923 -- initialized limited components, e.g. tasks. For other cases we
6924 -- create a temporary. A full analysis for safety of in-place assignment
6927 -- For allocators we assign to the designated object in place if the
6928 -- aggregate meets the same conditions as other in-place assignments.
6929 -- In this case the aggregate may not come from source but was created
6930 -- for default initialization, e.g. with Initialize_Scalars.
6932 if Requires_Transient_Scope
(Typ
) then
6933 Establish_Transient_Scope
(N
, Manage_Sec_Stack
=> False);
6936 -- An array of limited components is built in place
6938 if Is_Limited_Type
(Typ
) then
6939 Maybe_In_Place_OK
:= True;
6941 elsif Has_Default_Init_Comps
(N
) then
6942 Maybe_In_Place_OK
:= False;
6944 elsif Is_Bit_Packed_Array
(Typ
)
6945 or else Has_Controlled_Component
(Typ
)
6947 Maybe_In_Place_OK
:= False;
6949 elsif Parent_Kind
= N_Assignment_Statement
then
6950 Maybe_In_Place_OK
:=
6951 In_Place_Assign_OK
(N
, Get_Base_Object
(Name
(Parent_Node
)));
6953 elsif Parent_Kind
= N_Allocator
then
6954 Maybe_In_Place_OK
:= In_Place_Assign_OK
(N
);
6957 Maybe_In_Place_OK
:= False;
6960 -- If this is an array of tasks, it will be expanded into build-in-place
6961 -- assignments. Build an activation chain for the tasks now.
6963 if Has_Task
(Etype
(N
)) then
6964 Build_Activation_Chain_Entity
(N
);
6967 -- Perform in-place expansion of aggregate in an object declaration.
6968 -- Note: actions generated for the aggregate will be captured in an
6969 -- expression-with-actions statement so that they can be transferred
6970 -- to freeze actions later if there is an address clause for the
6971 -- object. (Note: we don't use a block statement because this would
6972 -- cause generated freeze nodes to be elaborated in the wrong scope).
6974 -- Arrays of limited components must be built in place. The code
6975 -- previously excluded controlled components but this is an old
6976 -- oversight: the rules in 7.6 (17) are clear.
6978 if Comes_From_Source
(Parent_Node
)
6979 and then Parent_Kind
= N_Object_Declaration
6980 and then Present
(Expression
(Parent_Node
))
6982 Must_Slide
(N
, Etype
(Defining_Identifier
(Parent_Node
)), Typ
)
6983 and then not Is_Bit_Packed_Array
(Typ
)
6985 In_Place_Assign_OK_For_Declaration
:= True;
6986 Tmp
:= Defining_Identifier
(Parent_Node
);
6987 Set_No_Initialization
(Parent_Node
);
6988 Set_Expression
(Parent_Node
, Empty
);
6990 -- Set kind and type of the entity, for use in the analysis
6991 -- of the subsequent assignments. If the nominal type is not
6992 -- constrained, build a subtype from the known bounds of the
6993 -- aggregate. If the declaration has a subtype mark, use it,
6994 -- otherwise use the itype of the aggregate.
6996 Mutate_Ekind
(Tmp
, E_Variable
);
6998 if not Is_Constrained
(Typ
) then
6999 Build_Constrained_Type
(Positional
=> False);
7001 elsif Is_Entity_Name
(Object_Definition
(Parent_Node
))
7002 and then Is_Constrained
(Entity
(Object_Definition
(Parent_Node
)))
7004 Set_Etype
(Tmp
, Entity
(Object_Definition
(Parent_Node
)));
7007 Set_Size_Known_At_Compile_Time
(Typ
, False);
7008 Set_Etype
(Tmp
, Typ
);
7011 elsif Maybe_In_Place_OK
and then Parent_Kind
= N_Allocator
then
7012 Set_Expansion_Delayed
(N
);
7015 -- Limited arrays in return statements are expanded when
7016 -- enclosing construct is expanded.
7018 elsif Maybe_In_Place_OK
7019 and then Parent_Kind
= N_Simple_Return_Statement
7021 Set_Expansion_Delayed
(N
);
7024 -- In the remaining cases the aggregate appears in the RHS of an
7025 -- assignment, which may be part of the expansion of an object
7026 -- declaration. If the aggregate is an actual in a call, itself
7027 -- possibly in a RHS, building it in the target is not possible.
7029 elsif Maybe_In_Place_OK
7030 and then Nkind
(Parent_Node
) not in N_Subprogram_Call
7031 and then Safe_Left_Hand_Side
(Name
(Parent_Node
))
7033 Tmp
:= Name
(Parent_Node
);
7035 if Etype
(Tmp
) /= Etype
(N
) then
7036 Apply_Length_Check
(N
, Etype
(Tmp
));
7038 if Nkind
(N
) = N_Raise_Constraint_Error
then
7040 -- Static error, nothing further to expand
7046 -- If a slice assignment has an aggregate with a single others_choice,
7047 -- the assignment can be done in place even if bounds are not static,
7048 -- by converting it into a loop over the discrete range of the slice.
7050 elsif Maybe_In_Place_OK
7051 and then Nkind
(Name
(Parent_Node
)) = N_Slice
7052 and then Is_Others_Aggregate
(N
)
7054 Tmp
:= Name
(Parent_Node
);
7056 -- Set type of aggregate to be type of lhs in assignment, in order
7057 -- to suppress redundant length checks.
7059 Set_Etype
(N
, Etype
(Tmp
));
7063 -- In-place aggregate expansion is not possible
7066 Maybe_In_Place_OK
:= False;
7067 Tmp
:= Make_Temporary
(Loc
, 'A', N
);
7069 Make_Object_Declaration
(Loc
,
7070 Defining_Identifier
=> Tmp
,
7071 Object_Definition
=> New_Occurrence_Of
(Typ
, Loc
));
7072 Set_No_Initialization
(Tmp_Decl
, True);
7074 -- If we are within a loop, the temporary will be pushed on the
7075 -- stack at each iteration. If the aggregate is the expression
7076 -- for an allocator, it will be immediately copied to the heap
7077 -- and can be reclaimed at once. We create a transient scope
7078 -- around the aggregate for this purpose.
7080 if Ekind
(Current_Scope
) = E_Loop
7081 and then Parent_Kind
= N_Allocator
7083 Establish_Transient_Scope
(N
, Manage_Sec_Stack
=> False);
7086 Insert_Action
(N
, Tmp_Decl
);
7089 -- Construct and insert the aggregate code. We can safely suppress index
7090 -- checks because this code is guaranteed not to raise CE on index
7091 -- checks. However we should *not* suppress all checks.
7097 if Nkind
(Tmp
) = N_Defining_Identifier
then
7098 Target
:= New_Occurrence_Of
(Tmp
, Loc
);
7101 if Has_Default_Init_Comps
(N
)
7102 and then not Maybe_In_Place_OK
7104 -- Ada 2005 (AI-287): This case has not been analyzed???
7106 raise Program_Error
;
7109 -- Name in assignment is explicit dereference
7111 Target
:= New_Copy
(Tmp
);
7114 -- If we are to generate an in-place assignment for a declaration or
7115 -- an assignment statement, and the assignment can be done directly
7116 -- by the back end, then do not expand further.
7118 -- ??? We can also do that if in-place expansion is not possible but
7119 -- then we could go into an infinite recursion.
7121 if (In_Place_Assign_OK_For_Declaration
or else Maybe_In_Place_OK
)
7122 and then not CodePeer_Mode
7123 and then not Modify_Tree_For_C
7124 and then not Possible_Bit_Aligned_Component
(Target
)
7125 and then not Is_Possibly_Unaligned_Slice
(Target
)
7126 and then Aggr_Assignment_OK_For_Backend
(N
)
7129 -- In the case of an assignment using an access with the
7130 -- Designated_Storage_Model aspect with a Copy_To procedure,
7131 -- insert a temporary and have the back end handle the assignment
7132 -- to it. Copy the result to the original target.
7134 if Parent_Kind
= N_Assignment_Statement
7135 and then Nkind
(Name
(Parent_Node
)) = N_Explicit_Dereference
7136 and then Has_Designated_Storage_Model_Aspect
7137 (Etype
(Prefix
(Name
(Parent_Node
))))
7138 and then Present
(Storage_Model_Copy_To
7139 (Storage_Model_Object
7140 (Etype
(Prefix
(Name
(Parent_Node
))))))
7142 Aggr_Code
:= Build_Assignment_With_Temporary
7143 (Target
, Typ
, New_Copy_Tree
(N
));
7146 if Maybe_In_Place_OK
then
7150 Aggr_Code
:= New_List
(
7151 Make_Assignment_Statement
(Loc
,
7153 Expression
=> New_Copy_Tree
(N
)));
7158 Build_Array_Aggr_Code
(N
,
7160 Index
=> First_Index
(Typ
),
7162 Scalar_Comp
=> Is_Scalar_Type
(Ctyp
));
7165 -- Save the last assignment statement associated with the aggregate
7166 -- when building a controlled object. This reference is utilized by
7167 -- the finalization machinery when marking an object as successfully
7170 if Needs_Finalization
(Typ
)
7171 and then Is_Entity_Name
(Target
)
7172 and then Present
(Entity
(Target
))
7173 and then Ekind
(Entity
(Target
)) in E_Constant | E_Variable
7175 Set_Last_Aggregate_Assignment
(Entity
(Target
), Last
(Aggr_Code
));
7179 -- If the aggregate is the expression in a declaration, the expanded
7180 -- code must be inserted after it. The defining entity might not come
7181 -- from source if this is part of an inlined body, but the declaration
7183 -- The test below looks very specialized and kludgy???
7185 if Comes_From_Source
(Tmp
)
7187 (Nkind
(Parent
(N
)) = N_Object_Declaration
7188 and then Comes_From_Source
(Parent
(N
))
7189 and then Tmp
= Defining_Entity
(Parent
(N
)))
7191 if Parent_Kind
/= N_Object_Declaration
or else Is_Frozen
(Tmp
) then
7192 Insert_Actions_After
(Parent_Node
, Aggr_Code
);
7195 Comp_Stmt
: constant Node_Id
:=
7196 Make_Compound_Statement
7197 (Sloc
(Parent_Node
), Actions
=> Aggr_Code
);
7199 Insert_Action_After
(Parent_Node
, Comp_Stmt
);
7200 Set_Initialization_Statements
(Tmp
, Comp_Stmt
);
7204 Insert_Actions
(N
, Aggr_Code
);
7207 -- If the aggregate has been assigned in place, remove the original
7210 if Parent_Kind
= N_Assignment_Statement
and then Maybe_In_Place_OK
then
7211 Rewrite
(Parent_Node
, Make_Null_Statement
(Loc
));
7213 -- Or else, if a temporary was created, replace the aggregate with it
7215 elsif Parent_Kind
/= N_Object_Declaration
7216 or else Tmp
/= Defining_Identifier
(Parent_Node
)
7218 Rewrite
(N
, New_Occurrence_Of
(Tmp
, Loc
));
7219 Analyze_And_Resolve
(N
, Typ
);
7221 end Expand_Array_Aggregate
;
7223 ------------------------
7224 -- Expand_N_Aggregate --
7225 ------------------------
7227 procedure Expand_N_Aggregate
(N
: Node_Id
) is
7228 T
: constant Entity_Id
:= Etype
(N
);
7230 -- Record aggregate case
7232 if Is_Record_Type
(T
)
7233 and then not Is_Private_Type
(T
)
7235 Expand_Record_Aggregate
(N
);
7237 elsif Has_Aspect
(T
, Aspect_Aggregate
) then
7238 Expand_Container_Aggregate
(N
);
7240 -- Array aggregate case
7243 -- A special case, if we have a string subtype with bounds 1 .. N,
7244 -- where N is known at compile time, and the aggregate is of the
7245 -- form (others => 'x'), with a single choice and no expressions,
7246 -- and N is less than 80 (an arbitrary limit for now), then replace
7247 -- the aggregate by the equivalent string literal (but do not mark
7248 -- it as static since it is not).
7250 -- Note: this entire circuit is redundant with respect to code in
7251 -- Expand_Array_Aggregate that collapses others choices to positional
7252 -- form, but there are two problems with that circuit:
7254 -- a) It is limited to very small cases due to ill-understood
7255 -- interactions with bootstrapping. That limit is removed by
7256 -- use of the No_Implicit_Loops restriction.
7258 -- b) It incorrectly ends up with the resulting expressions being
7259 -- considered static when they are not. For example, the
7260 -- following test should fail:
7262 -- pragma Restrictions (No_Implicit_Loops);
7263 -- package NonSOthers4 is
7264 -- B : constant String (1 .. 6) := (others => 'A');
7265 -- DH : constant String (1 .. 8) := B & "BB";
7267 -- pragma Export (C, X, Link_Name => DH);
7270 -- But it succeeds (DH looks static to pragma Export)
7272 -- To be sorted out ???
7274 if Present
(Component_Associations
(N
)) then
7276 CA
: constant Node_Id
:= First
(Component_Associations
(N
));
7277 MX
: constant := 80;
7281 and then Nkind
(First
(Choice_List
(CA
))) = N_Others_Choice
7282 and then Nkind
(Expression
(CA
)) = N_Character_Literal
7283 and then No
(Expressions
(N
))
7286 X
: constant Node_Id
:= First_Index
(T
);
7287 EC
: constant Node_Id
:= Expression
(CA
);
7288 CV
: constant Uint
:= Char_Literal_Value
(EC
);
7289 CC
: constant Char_Code
:= UI_To_CC
(CV
);
7292 if Nkind
(X
) = N_Range
7293 and then Compile_Time_Known_Value
(Low_Bound
(X
))
7294 and then Expr_Value
(Low_Bound
(X
)) = 1
7295 and then Compile_Time_Known_Value
(High_Bound
(X
))
7298 Hi
: constant Uint
:= Expr_Value
(High_Bound
(X
));
7304 for J
in 1 .. UI_To_Int
(Hi
) loop
7305 Store_String_Char
(CC
);
7309 Make_String_Literal
(Sloc
(N
),
7310 Strval
=> End_String
));
7312 if In_Character_Range
(CC
) then
7314 elsif In_Wide_Character_Range
(CC
) then
7315 Set_Has_Wide_Character
(N
);
7317 Set_Has_Wide_Wide_Character
(N
);
7320 Analyze_And_Resolve
(N
, T
);
7321 Set_Is_Static_Expression
(N
, False);
7331 -- Not that special case, so normal expansion of array aggregate
7333 Expand_Array_Aggregate
(N
);
7337 when RE_Not_Available
=>
7339 end Expand_N_Aggregate
;
7341 --------------------------------
7342 -- Expand_Container_Aggregate --
7343 --------------------------------
7345 procedure Expand_Container_Aggregate
(N
: Node_Id
) is
7346 Loc
: constant Source_Ptr
:= Sloc
(N
);
7347 Typ
: constant Entity_Id
:= Etype
(N
);
7348 Asp
: constant Node_Id
:= Find_Value_Of_Aspect
(Typ
, Aspect_Aggregate
);
7350 Empty_Subp
: Node_Id
:= Empty
;
7351 Add_Named_Subp
: Node_Id
:= Empty
;
7352 Add_Unnamed_Subp
: Node_Id
:= Empty
;
7353 New_Indexed_Subp
: Node_Id
:= Empty
;
7354 Assign_Indexed_Subp
: Node_Id
:= Empty
;
7356 Aggr_Code
: constant List_Id
:= New_List
;
7357 Temp
: constant Entity_Id
:= Make_Temporary
(Loc
, 'C', N
);
7362 Init_Stat
: Node_Id
;
7365 -- The following are used when the size of the aggregate is not
7366 -- static and requires a dynamic evaluation.
7368 Siz_Exp
: Node_Id
:= Empty
;
7369 Count_Type
: Entity_Id
;
7371 function Aggregate_Size
return Int
;
7372 -- Compute number of entries in aggregate, including choices
7373 -- that cover a range or subtype, as well as iterated constructs.
7374 -- Return -1 if the size is not known statically, in which case
7375 -- allocate a default size for the aggregate, or build an expression
7376 -- to estimate the size dynamically.
7378 function Build_Siz_Exp
(Comp
: Node_Id
) return Int
;
7379 -- When the aggregate contains a single Iterated_Component_Association
7380 -- or Element_Association with non-static bounds, build an expression
7381 -- to be used as the allocated size of the container. This may be an
7382 -- overestimate if a filter is present, but is a safe approximation.
7383 -- If bounds are dynamic the aggregate is created in two passes, and
7384 -- the first generates a loop for the sole purpose of computing the
7385 -- number of elements that will be generated on the second pass.
7387 procedure Expand_Iterated_Component
(Comp
: Node_Id
);
7388 -- Handle iterated_component_association and iterated_Element
7389 -- association by generating a loop over the specified range,
7390 -- given either by a loop parameter specification or an iterator
7393 --------------------
7394 -- Aggregate_Size --
7395 --------------------
7397 function Aggregate_Size
return Int
is
7403 procedure Add_Range_Size
;
7404 -- Compute number of components specified by a component association
7405 -- given by a range or subtype name.
7407 --------------------
7408 -- Add_Range_Size --
7409 --------------------
7411 procedure Add_Range_Size
is
7413 -- The bounds of the discrete range are integers or enumeration
7416 if Nkind
(Lo
) = N_Integer_Literal
then
7417 Siz
:= Siz
+ UI_To_Int
(Intval
(Hi
))
7418 - UI_To_Int
(Intval
(Lo
)) + 1;
7420 Siz
:= Siz
+ UI_To_Int
(Enumeration_Pos
(Hi
))
7421 - UI_To_Int
(Enumeration_Pos
(Lo
)) + 1;
7426 -- Aggregate is either all positional or all named
7428 Siz
:= List_Length
(Expressions
(N
));
7430 if Present
(Component_Associations
(N
)) then
7431 Comp
:= First
(Component_Associations
(N
));
7432 -- If there is a single component association it can be
7433 -- an iterated component with dynamic bounds or an element
7434 -- iterator over an iterable object. If it is an array
7435 -- we can use the attribute Length to get its size;
7436 -- for a predefined container the function Length plays
7437 -- the same role. There is no available mechanism for
7438 -- user-defined containers. For now we treat all of these
7441 if List_Length
(Component_Associations
(N
)) = 1
7442 and then Nkind
(Comp
) in N_Iterated_Component_Association |
7443 N_Iterated_Element_Association
7445 return Build_Siz_Exp
(Comp
);
7448 -- Otherwise all associations must specify static sizes.
7450 while Present
(Comp
) loop
7451 Choice
:= First
(Choice_List
(Comp
));
7453 while Present
(Choice
) loop
7456 if Nkind
(Choice
) = N_Range
then
7457 Lo
:= Low_Bound
(Choice
);
7458 Hi
:= High_Bound
(Choice
);
7461 elsif Is_Entity_Name
(Choice
)
7462 and then Is_Type
(Entity
(Choice
))
7464 Lo
:= Type_Low_Bound
(Entity
(Choice
));
7465 Hi
:= Type_High_Bound
(Entity
(Choice
));
7471 New_Copy_Tree
(Hi
)));
7474 -- Single choice (syntax excludes a subtype
7493 function Build_Siz_Exp
(Comp
: Node_Id
) return Int
is
7496 if Nkind
(Comp
) = N_Range
then
7497 Lo
:= Low_Bound
(Comp
);
7498 Hi
:= High_Bound
(Comp
);
7502 -- Compute static size when possible.
7504 if Is_Static_Expression
(Lo
)
7505 and then Is_Static_Expression
(Hi
)
7507 if Nkind
(Lo
) = N_Integer_Literal
then
7508 Siz
:= UI_To_Int
(Intval
(Hi
)) - UI_To_Int
(Intval
(Lo
)) + 1;
7510 Siz
:= UI_To_Int
(Enumeration_Pos
(Hi
))
7511 - UI_To_Int
(Enumeration_Pos
(Lo
)) + 1;
7517 Make_Op_Add
(Sloc
(Comp
),
7519 Make_Op_Subtract
(Sloc
(Comp
),
7520 Left_Opnd
=> New_Copy_Tree
(Hi
),
7521 Right_Opnd
=> New_Copy_Tree
(Lo
)),
7523 Make_Integer_Literal
(Loc
, 1));
7527 elsif Nkind
(Comp
) = N_Iterated_Component_Association
then
7528 return Build_Siz_Exp
(First
(Discrete_Choices
(Comp
)));
7530 elsif Nkind
(Comp
) = N_Iterated_Element_Association
then
7533 -- ??? Need to create code for a loop and add to generated code,
7534 -- as is done for array aggregates with iterated element
7535 -- associations, instead of using Append operations.
7542 -------------------------------
7543 -- Expand_Iterated_Component --
7544 -------------------------------
7546 procedure Expand_Iterated_Component
(Comp
: Node_Id
) is
7547 Expr
: constant Node_Id
:= Expression
(Comp
);
7549 Key_Expr
: Node_Id
:= Empty
;
7550 Loop_Id
: Entity_Id
;
7552 L_Iteration_Scheme
: Node_Id
;
7553 Loop_Stat
: Node_Id
;
7558 if Nkind
(Comp
) = N_Iterated_Element_Association
then
7559 Key_Expr
:= Key_Expression
(Comp
);
7561 -- We create a new entity as loop identifier in all cases,
7562 -- as is done for generated loops elsewhere, as the loop
7563 -- structure has been previously analyzed.
7565 if Present
(Iterator_Specification
(Comp
)) then
7567 -- Either an Iterator_Specification or a Loop_Parameter_
7568 -- Specification is present.
7570 L_Iteration_Scheme
:=
7571 Make_Iteration_Scheme
(Loc
,
7572 Iterator_Specification
=> Iterator_Specification
(Comp
));
7574 Make_Defining_Identifier
(Loc
,
7575 Chars
=> Chars
(Defining_Identifier
7576 (Iterator_Specification
(Comp
))));
7577 Set_Defining_Identifier
7578 (Iterator_Specification
(L_Iteration_Scheme
), Loop_Id
);
7581 L_Iteration_Scheme
:=
7582 Make_Iteration_Scheme
(Loc
,
7583 Loop_Parameter_Specification
=>
7584 Loop_Parameter_Specification
(Comp
));
7586 Make_Defining_Identifier
(Loc
,
7587 Chars
=> Chars
(Defining_Identifier
7588 (Loop_Parameter_Specification
(Comp
))));
7589 Set_Defining_Identifier
7590 (Loop_Parameter_Specification
7591 (L_Iteration_Scheme
), Loop_Id
);
7595 -- Iterated_Component_Association.
7597 if Present
(Iterator_Specification
(Comp
)) then
7599 Make_Defining_Identifier
(Loc
,
7600 Chars
=> Chars
(Defining_Identifier
7601 (Iterator_Specification
(Comp
))));
7602 L_Iteration_Scheme
:=
7603 Make_Iteration_Scheme
(Loc
,
7604 Iterator_Specification
=> Iterator_Specification
(Comp
));
7607 -- Loop_Parameter_Specification is parsed with a choice list.
7608 -- where the range is the first (and only) choice.
7611 Make_Defining_Identifier
(Loc
,
7612 Chars
=> Chars
(Defining_Identifier
(Comp
)));
7613 L_Range
:= Relocate_Node
(First
(Discrete_Choices
(Comp
)));
7615 L_Iteration_Scheme
:=
7616 Make_Iteration_Scheme
(Loc
,
7617 Loop_Parameter_Specification
=>
7618 Make_Loop_Parameter_Specification
(Loc
,
7619 Defining_Identifier
=> Loop_Id
,
7620 Discrete_Subtype_Definition
=> L_Range
));
7624 -- Build insertion statement. For a positional aggregate, only the
7625 -- expression is needed. For a named aggregate, the loop variable,
7626 -- whose type is that of the key, is an additional parameter for
7627 -- the insertion operation.
7628 -- If a Key_Expression is present, it serves as the additional
7629 -- parameter. Otherwise the key is given by the loop parameter
7632 if Present
(Add_Unnamed_Subp
)
7633 and then No
(Add_Named_Subp
)
7636 (Make_Procedure_Call_Statement
(Loc
,
7637 Name
=> New_Occurrence_Of
(Entity
(Add_Unnamed_Subp
), Loc
),
7638 Parameter_Associations
=>
7639 New_List
(New_Occurrence_Of
(Temp
, Loc
),
7640 New_Copy_Tree
(Expr
))));
7642 -- Named or indexed aggregate, for which a key is present,
7643 -- possibly with a specified key_expression.
7645 if Present
(Key_Expr
) then
7646 Params
:= New_List
(New_Occurrence_Of
(Temp
, Loc
),
7647 New_Copy_Tree
(Key_Expr
),
7648 New_Copy_Tree
(Expr
));
7650 Params
:= New_List
(New_Occurrence_Of
(Temp
, Loc
),
7651 New_Occurrence_Of
(Loop_Id
, Loc
),
7652 New_Copy_Tree
(Expr
));
7656 (Make_Procedure_Call_Statement
(Loc
,
7657 Name
=> New_Occurrence_Of
(Entity
(Add_Named_Subp
), Loc
),
7658 Parameter_Associations
=> Params
));
7661 Loop_Stat
:= Make_Implicit_Loop_Statement
7663 Identifier
=> Empty
,
7664 Iteration_Scheme
=> L_Iteration_Scheme
,
7665 Statements
=> Stats
);
7666 Append
(Loop_Stat
, Aggr_Code
);
7668 end Expand_Iterated_Component
;
7670 -- Start of processing for Expand_Container_Aggregate
7673 Parse_Aspect_Aggregate
(Asp
,
7674 Empty_Subp
, Add_Named_Subp
, Add_Unnamed_Subp
,
7675 New_Indexed_Subp
, Assign_Indexed_Subp
);
7677 -- The constructor for bounded containers is a function with
7678 -- a parameter that sets the size of the container. If the
7679 -- size cannot be determined statically we use a default value
7680 -- or a dynamic expression.
7682 Siz
:= Aggregate_Size
;
7684 if Ekind
(Entity
(Empty_Subp
)) = E_Function
7685 and then Present
(First_Formal
(Entity
(Empty_Subp
)))
7687 Default
:= Default_Value
(First_Formal
(Entity
(Empty_Subp
)));
7689 -- If aggregate size is not static, we can use default value
7690 -- of formal parameter for allocation. We assume that this
7691 -- (implementation-dependent) value is static, even though
7692 -- the AI does not require it.
7694 -- Create declaration for size: a constant literal in the simple
7695 -- case, an expression if iterated component associations may be
7696 -- involved, the default otherwise.
7698 Count_Type
:= Etype
(First_Formal
(Entity
(Empty_Subp
)));
7700 if No
(Siz_Exp
) then
7701 Siz
:= UI_To_Int
(Intval
(Default
));
7702 Siz_Exp
:= Make_Integer_Literal
(Loc
, Siz
);
7705 Siz_Exp
:= Make_Type_Conversion
(Loc
,
7707 New_Occurrence_Of
(Count_Type
, Loc
),
7708 Expression
=> Siz_Exp
);
7712 Siz_Exp
:= Make_Integer_Literal
(Loc
, Siz
);
7715 Siz_Decl
:= Make_Object_Declaration
(Loc
,
7716 Defining_Identifier
=> Make_Temporary
(Loc
, 'S', N
),
7717 Object_Definition
=>
7718 New_Occurrence_Of
(Count_Type
, Loc
),
7719 Expression
=> Siz_Exp
);
7720 Append
(Siz_Decl
, Aggr_Code
);
7722 if Nkind
(Siz_Exp
) = N_Integer_Literal
then
7724 Make_Object_Declaration
(Loc
,
7725 Defining_Identifier
=> Temp
,
7726 Object_Definition
=> New_Occurrence_Of
(Typ
, Loc
),
7727 Expression
=> Make_Function_Call
(Loc
,
7728 Name
=> New_Occurrence_Of
(Entity
(Empty_Subp
), Loc
),
7729 Parameter_Associations
=>
7732 (Defining_Identifier
(Siz_Decl
), Loc
))));
7736 Make_Object_Declaration
(Loc
,
7737 Defining_Identifier
=> Temp
,
7738 Object_Definition
=> New_Occurrence_Of
(Typ
, Loc
),
7739 Expression
=> Make_Function_Call
(Loc
,
7741 New_Occurrence_Of
(Entity
(New_Indexed_Subp
), Loc
),
7742 Parameter_Associations
=>
7744 Make_Integer_Literal
(Loc
, 1),
7746 (Defining_Identifier
(Siz_Decl
), Loc
))));
7749 Append
(Init_Stat
, Aggr_Code
);
7751 -- Size is dynamic: Create declaration for object, and intitialize
7752 -- with a call to the null container, or an assignment to it.
7756 Make_Object_Declaration
(Loc
,
7757 Defining_Identifier
=> Temp
,
7758 Object_Definition
=> New_Occurrence_Of
(Typ
, Loc
));
7760 Insert_Action
(N
, Decl
);
7762 -- The Empty entity is either a parameterless function, or
7765 if Ekind
(Entity
(Empty_Subp
)) = E_Function
then
7766 Init_Stat
:= Make_Assignment_Statement
(Loc
,
7767 Name
=> New_Occurrence_Of
(Temp
, Loc
),
7768 Expression
=> Make_Function_Call
(Loc
,
7769 Name
=> New_Occurrence_Of
(Entity
(Empty_Subp
), Loc
)));
7772 Init_Stat
:= Make_Assignment_Statement
(Loc
,
7773 Name
=> New_Occurrence_Of
(Temp
, Loc
),
7774 Expression
=> New_Occurrence_Of
(Entity
(Empty_Subp
), Loc
));
7777 Append
(Init_Stat
, Aggr_Code
);
7780 ---------------------------
7781 -- Positional aggregate --
7782 ---------------------------
7784 -- If the aggregate is positional the aspect must include
7785 -- an Add_Unnamed subprogram.
7787 if Present
(Add_Unnamed_Subp
) then
7788 if Present
(Expressions
(N
)) then
7790 Insert
: constant Entity_Id
:= Entity
(Add_Unnamed_Subp
);
7795 Comp
:= First
(Expressions
(N
));
7796 while Present
(Comp
) loop
7797 Stat
:= Make_Procedure_Call_Statement
(Loc
,
7798 Name
=> New_Occurrence_Of
(Insert
, Loc
),
7799 Parameter_Associations
=>
7800 New_List
(New_Occurrence_Of
(Temp
, Loc
),
7801 New_Copy_Tree
(Comp
)));
7802 Append
(Stat
, Aggr_Code
);
7808 -- Indexed aggregates are handled below. Unnamed aggregates
7809 -- such as sets may include iterated component associations.
7811 if No
(New_Indexed_Subp
) then
7812 Comp
:= First
(Component_Associations
(N
));
7813 while Present
(Comp
) loop
7814 if Nkind
(Comp
) = N_Iterated_Component_Association
then
7815 Expand_Iterated_Component
(Comp
);
7821 ---------------------
7822 -- Named_Aggregate --
7823 ---------------------
7825 elsif Present
(Add_Named_Subp
) then
7827 Insert
: constant Entity_Id
:= Entity
(Add_Named_Subp
);
7831 Comp
:= First
(Component_Associations
(N
));
7833 -- Each component association may contain several choices;
7834 -- generate an insertion statement for each.
7836 while Present
(Comp
) loop
7837 if Nkind
(Comp
) in N_Iterated_Component_Association
7838 | N_Iterated_Element_Association
7840 Expand_Iterated_Component
(Comp
);
7842 Key
:= First
(Choices
(Comp
));
7844 while Present
(Key
) loop
7845 Stat
:= Make_Procedure_Call_Statement
(Loc
,
7846 Name
=> New_Occurrence_Of
(Insert
, Loc
),
7847 Parameter_Associations
=>
7848 New_List
(New_Occurrence_Of
(Temp
, Loc
),
7849 New_Copy_Tree
(Key
),
7850 New_Copy_Tree
(Expression
(Comp
))));
7851 Append
(Stat
, Aggr_Code
);
7862 -----------------------
7863 -- Indexed_Aggregate --
7864 -----------------------
7866 -- For an indexed aggregate there must be an Assigned_Indexeed
7867 -- subprogram. Note that unlike array aggregates, a container
7868 -- aggregate must be fully positional or fully indexed. In the
7869 -- first case the expansion has already taken place.
7870 -- TBA: the keys for an indexed aggregate must provide a dense
7871 -- range with no repetitions.
7873 if Present
(Assign_Indexed_Subp
)
7874 and then Present
(Component_Associations
(N
))
7877 Insert
: constant Entity_Id
:= Entity
(Assign_Indexed_Subp
);
7878 Index_Type
: constant Entity_Id
:=
7879 Etype
(Next_Formal
(First_Formal
(Insert
)));
7881 function Expand_Range_Component
7883 Expr
: Node_Id
) return Node_Id
;
7884 -- Transform a component assoication with a range into an
7885 -- explicit loop. If the choice is a subtype name, it is
7886 -- rewritten as a range with the corresponding bounds, which
7887 -- are known to be static.
7895 -----------------------------
7896 -- Expand_Raange_Component --
7897 -----------------------------
7899 function Expand_Range_Component
7901 Expr
: Node_Id
) return Node_Id
7903 Loop_Id
: constant Entity_Id
:=
7904 Make_Temporary
(Loc
, 'T');
7906 L_Iteration_Scheme
: Node_Id
;
7910 L_Iteration_Scheme
:=
7911 Make_Iteration_Scheme
(Loc
,
7912 Loop_Parameter_Specification
=>
7913 Make_Loop_Parameter_Specification
(Loc
,
7914 Defining_Identifier
=> Loop_Id
,
7915 Discrete_Subtype_Definition
=> New_Copy_Tree
(Rng
)));
7918 (Make_Procedure_Call_Statement
(Loc
,
7920 New_Occurrence_Of
(Entity
(Assign_Indexed_Subp
), Loc
),
7921 Parameter_Associations
=>
7922 New_List
(New_Occurrence_Of
(Temp
, Loc
),
7923 New_Occurrence_Of
(Loop_Id
, Loc
),
7924 New_Copy_Tree
(Expr
))));
7926 return Make_Implicit_Loop_Statement
7928 Identifier
=> Empty
,
7929 Iteration_Scheme
=> L_Iteration_Scheme
,
7930 Statements
=> Stats
);
7931 end Expand_Range_Component
;
7936 -- Modify the call to the constructor to allocate the
7937 -- required size for the aggregwte : call the provided
7938 -- constructor rather than the Empty aggregate.
7940 Index
:= Make_Op_Add
(Loc
,
7941 Left_Opnd
=> New_Copy_Tree
(Type_Low_Bound
(Index_Type
)),
7942 Right_Opnd
=> Make_Integer_Literal
(Loc
, Siz
- 1));
7944 Set_Expression
(Init_Stat
,
7945 Make_Function_Call
(Loc
,
7947 New_Occurrence_Of
(Entity
(New_Indexed_Subp
), Loc
),
7948 Parameter_Associations
=>
7950 New_Copy_Tree
(Type_Low_Bound
(Index_Type
)),
7954 if Present
(Expressions
(N
)) then
7955 Comp
:= First
(Expressions
(N
));
7957 while Present
(Comp
) loop
7959 -- Compute index position for successive components
7960 -- in the list of expressions, and use the indexed
7961 -- assignment procedure for each.
7963 Index
:= Make_Op_Add
(Loc
,
7964 Left_Opnd
=> Type_Low_Bound
(Index_Type
),
7965 Right_Opnd
=> Make_Integer_Literal
(Loc
, Pos
));
7967 Stat
:= Make_Procedure_Call_Statement
(Loc
,
7968 Name
=> New_Occurrence_Of
(Insert
, Loc
),
7969 Parameter_Associations
=>
7970 New_List
(New_Occurrence_Of
(Temp
, Loc
),
7972 New_Copy_Tree
(Comp
)));
7976 Append
(Stat
, Aggr_Code
);
7981 if Present
(Component_Associations
(N
)) then
7982 Comp
:= First
(Component_Associations
(N
));
7984 -- The choice may be a static value, or a range with
7987 while Present
(Comp
) loop
7988 if Nkind
(Comp
) = N_Component_Association
then
7989 Key
:= First
(Choices
(Comp
));
7990 while Present
(Key
) loop
7992 -- If the expression is a box, the corresponding
7993 -- component (s) is left uninitialized.
7995 if Box_Present
(Comp
) then
7998 elsif Nkind
(Key
) = N_Range
then
8000 -- Create loop for tne specified range,
8001 -- with copies of the expression.
8004 Expand_Range_Component
(Key
, Expression
(Comp
));
8007 Stat
:= Make_Procedure_Call_Statement
(Loc
,
8008 Name
=> New_Occurrence_Of
8009 (Entity
(Assign_Indexed_Subp
), Loc
),
8010 Parameter_Associations
=>
8011 New_List
(New_Occurrence_Of
(Temp
, Loc
),
8012 New_Copy_Tree
(Key
),
8013 New_Copy_Tree
(Expression
(Comp
))));
8016 Append
(Stat
, Aggr_Code
);
8023 -- Iterated component association. Discard
8024 -- positional insertion procedure.
8026 Add_Named_Subp
:= Assign_Indexed_Subp
;
8027 Add_Unnamed_Subp
:= Empty
;
8028 Expand_Iterated_Component
(Comp
);
8037 Insert_Actions
(N
, Aggr_Code
);
8038 Rewrite
(N
, New_Occurrence_Of
(Temp
, Loc
));
8039 Analyze_And_Resolve
(N
, Typ
);
8040 end Expand_Container_Aggregate
;
8042 ------------------------------
8043 -- Expand_N_Delta_Aggregate --
8044 ------------------------------
8046 procedure Expand_N_Delta_Aggregate
(N
: Node_Id
) is
8047 Loc
: constant Source_Ptr
:= Sloc
(N
);
8048 Typ
: constant Entity_Id
:= Etype
(Expression
(N
));
8053 Make_Object_Declaration
(Loc
,
8054 Defining_Identifier
=> Make_Temporary
(Loc
, 'T'),
8055 Object_Definition
=> New_Occurrence_Of
(Typ
, Loc
),
8056 Expression
=> New_Copy_Tree
(Expression
(N
)));
8058 if Is_Array_Type
(Etype
(N
)) then
8059 Expand_Delta_Array_Aggregate
(N
, New_List
(Decl
));
8061 Expand_Delta_Record_Aggregate
(N
, New_List
(Decl
));
8063 end Expand_N_Delta_Aggregate
;
8065 ----------------------------------
8066 -- Expand_Delta_Array_Aggregate --
8067 ----------------------------------
8069 procedure Expand_Delta_Array_Aggregate
(N
: Node_Id
; Deltas
: List_Id
) is
8070 Loc
: constant Source_Ptr
:= Sloc
(N
);
8071 Temp
: constant Entity_Id
:= Defining_Identifier
(First
(Deltas
));
8074 function Generate_Loop
(C
: Node_Id
) return Node_Id
;
8075 -- Generate a loop containing individual component assignments for
8076 -- choices that are ranges, subtype indications, subtype names, and
8077 -- iterated component associations.
8083 function Generate_Loop
(C
: Node_Id
) return Node_Id
is
8084 Sl
: constant Source_Ptr
:= Sloc
(C
);
8088 if Nkind
(Parent
(C
)) = N_Iterated_Component_Association
then
8090 Make_Defining_Identifier
(Loc
,
8091 Chars
=> (Chars
(Defining_Identifier
(Parent
(C
)))));
8093 Ix
:= Make_Temporary
(Sl
, 'I');
8097 Make_Implicit_Loop_Statement
(C
,
8099 Make_Iteration_Scheme
(Sl
,
8100 Loop_Parameter_Specification
=>
8101 Make_Loop_Parameter_Specification
(Sl
,
8102 Defining_Identifier
=> Ix
,
8103 Discrete_Subtype_Definition
=> New_Copy_Tree
(C
))),
8105 Statements
=> New_List
(
8106 Make_Assignment_Statement
(Sl
,
8108 Make_Indexed_Component
(Sl
,
8109 Prefix
=> New_Occurrence_Of
(Temp
, Sl
),
8110 Expressions
=> New_List
(New_Occurrence_Of
(Ix
, Sl
))),
8111 Expression
=> New_Copy_Tree
(Expression
(Assoc
)))),
8112 End_Label
=> Empty
);
8119 -- Start of processing for Expand_Delta_Array_Aggregate
8122 Assoc
:= First
(Component_Associations
(N
));
8123 while Present
(Assoc
) loop
8124 Choice
:= First
(Choice_List
(Assoc
));
8125 if Nkind
(Assoc
) = N_Iterated_Component_Association
then
8126 while Present
(Choice
) loop
8127 Append_To
(Deltas
, Generate_Loop
(Choice
));
8132 while Present
(Choice
) loop
8134 -- Choice can be given by a range, a subtype indication, a
8135 -- subtype name, a scalar value, or an entity.
8137 if Nkind
(Choice
) = N_Range
8138 or else (Is_Entity_Name
(Choice
)
8139 and then Is_Type
(Entity
(Choice
)))
8141 Append_To
(Deltas
, Generate_Loop
(Choice
));
8143 elsif Nkind
(Choice
) = N_Subtype_Indication
then
8145 Generate_Loop
(Range_Expression
(Constraint
(Choice
))));
8149 Make_Assignment_Statement
(Sloc
(Choice
),
8151 Make_Indexed_Component
(Sloc
(Choice
),
8152 Prefix
=> New_Occurrence_Of
(Temp
, Loc
),
8153 Expressions
=> New_List
(New_Copy_Tree
(Choice
))),
8154 Expression
=> New_Copy_Tree
(Expression
(Assoc
))));
8164 Insert_Actions
(N
, Deltas
);
8165 Rewrite
(N
, New_Occurrence_Of
(Temp
, Loc
));
8166 end Expand_Delta_Array_Aggregate
;
8168 -----------------------------------
8169 -- Expand_Delta_Record_Aggregate --
8170 -----------------------------------
8172 procedure Expand_Delta_Record_Aggregate
(N
: Node_Id
; Deltas
: List_Id
) is
8173 Loc
: constant Source_Ptr
:= Sloc
(N
);
8174 Temp
: constant Entity_Id
:= Defining_Identifier
(First
(Deltas
));
8179 Assoc
:= First
(Component_Associations
(N
));
8181 while Present
(Assoc
) loop
8182 Choice
:= First
(Choice_List
(Assoc
));
8183 while Present
(Choice
) loop
8185 Make_Assignment_Statement
(Sloc
(Choice
),
8187 Make_Selected_Component
(Sloc
(Choice
),
8188 Prefix
=> New_Occurrence_Of
(Temp
, Loc
),
8189 Selector_Name
=> Make_Identifier
(Loc
, Chars
(Choice
))),
8190 Expression
=> New_Copy_Tree
(Expression
(Assoc
))));
8197 Insert_Actions
(N
, Deltas
);
8198 Rewrite
(N
, New_Occurrence_Of
(Temp
, Loc
));
8199 end Expand_Delta_Record_Aggregate
;
8201 ----------------------------------
8202 -- Expand_N_Extension_Aggregate --
8203 ----------------------------------
8205 -- If the ancestor part is an expression, add a component association for
8206 -- the parent field. If the type of the ancestor part is not the direct
8207 -- parent of the expected type, build recursively the needed ancestors.
8208 -- If the ancestor part is a subtype_mark, replace aggregate with a
8209 -- declaration for a temporary of the expected type, followed by
8210 -- individual assignments to the given components.
8212 procedure Expand_N_Extension_Aggregate
(N
: Node_Id
) is
8213 A
: constant Node_Id
:= Ancestor_Part
(N
);
8214 Loc
: constant Source_Ptr
:= Sloc
(N
);
8215 Typ
: constant Entity_Id
:= Etype
(N
);
8218 -- If the ancestor is a subtype mark, an init proc must be called
8219 -- on the resulting object which thus has to be materialized in
8222 if Is_Entity_Name
(A
) and then Is_Type
(Entity
(A
)) then
8223 Convert_To_Assignments
(N
, Typ
);
8225 -- The extension aggregate is transformed into a record aggregate
8226 -- of the following form (c1 and c2 are inherited components)
8228 -- (Exp with c3 => a, c4 => b)
8229 -- ==> (c1 => Exp.c1, c2 => Exp.c2, c3 => a, c4 => b)
8234 if Tagged_Type_Expansion
then
8235 Expand_Record_Aggregate
(N
,
8238 (Node
(First_Elmt
(Access_Disp_Table
(Typ
))), Loc
),
8241 -- No tag is needed in the case of a VM
8244 Expand_Record_Aggregate
(N
, Parent_Expr
=> A
);
8249 when RE_Not_Available
=>
8251 end Expand_N_Extension_Aggregate
;
8253 -----------------------------
8254 -- Expand_Record_Aggregate --
8255 -----------------------------
8257 procedure Expand_Record_Aggregate
8259 Orig_Tag
: Node_Id
:= Empty
;
8260 Parent_Expr
: Node_Id
:= Empty
)
8262 Loc
: constant Source_Ptr
:= Sloc
(N
);
8263 Comps
: constant List_Id
:= Component_Associations
(N
);
8264 Typ
: constant Entity_Id
:= Etype
(N
);
8265 Base_Typ
: constant Entity_Id
:= Base_Type
(Typ
);
8267 Static_Components
: Boolean := True;
8268 -- Flag to indicate whether all components are compile-time known,
8269 -- and the aggregate can be constructed statically and handled by
8270 -- the back-end. Set to False by Component_OK_For_Backend.
8272 procedure Build_Back_End_Aggregate
;
8273 -- Build a proper aggregate to be handled by the back-end
8275 function Compile_Time_Known_Composite_Value
(N
: Node_Id
) return Boolean;
8276 -- Returns true if N is an expression of composite type which can be
8277 -- fully evaluated at compile time without raising constraint error.
8278 -- Such expressions can be passed as is to Gigi without any expansion.
8280 -- This returns true for N_Aggregate with Compile_Time_Known_Aggregate
8281 -- set and constants whose expression is such an aggregate, recursively.
8283 function Component_OK_For_Backend
return Boolean;
8284 -- Check for presence of a component which makes it impossible for the
8285 -- backend to process the aggregate, thus requiring the use of a series
8286 -- of assignment statements. Cases checked for are a nested aggregate
8287 -- needing Late_Expansion, the presence of a tagged component which may
8288 -- need tag adjustment, and a bit unaligned component reference.
8290 -- We also force expansion into assignments if a component is of a
8291 -- mutable type (including a private type with discriminants) because
8292 -- in that case the size of the component to be copied may be smaller
8293 -- than the side of the target, and there is no simple way for gigi
8294 -- to compute the size of the object to be copied.
8296 -- NOTE: This is part of the ongoing work to define precisely the
8297 -- interface between front-end and back-end handling of aggregates.
8298 -- In general it is desirable to pass aggregates as they are to gigi,
8299 -- in order to minimize elaboration code. This is one case where the
8300 -- semantics of Ada complicate the analysis and lead to anomalies in
8301 -- the gcc back-end if the aggregate is not expanded into assignments.
8303 -- NOTE: This sets the global Static_Components to False in most, but
8304 -- not all, cases when it returns False.
8306 function Has_Per_Object_Constraint
(L
: List_Id
) return Boolean;
8307 -- Return True if any element of L has Has_Per_Object_Constraint set.
8308 -- L should be the Choices component of an N_Component_Association.
8310 function Has_Visible_Private_Ancestor
(Id
: E
) return Boolean;
8311 -- If any ancestor of the current type is private, the aggregate
8312 -- cannot be built in place. We cannot rely on Has_Private_Ancestor,
8313 -- because it will not be set when type and its parent are in the
8314 -- same scope, and the parent component needs expansion.
8316 function Top_Level_Aggregate
(N
: Node_Id
) return Node_Id
;
8317 -- For nested aggregates return the ultimate enclosing aggregate; for
8318 -- non-nested aggregates return N.
8320 ------------------------------
8321 -- Build_Back_End_Aggregate --
8322 ------------------------------
8324 procedure Build_Back_End_Aggregate
is
8327 Tag_Value
: Node_Id
;
8330 if Nkind
(N
) = N_Aggregate
then
8332 -- If the aggregate is static and can be handled by the back-end,
8333 -- nothing left to do.
8335 if Static_Components
then
8336 Set_Compile_Time_Known_Aggregate
(N
);
8337 Set_Expansion_Delayed
(N
, False);
8341 -- If no discriminants, nothing special to do
8343 if not Has_Discriminants
(Typ
) then
8346 -- Case of discriminants present
8348 elsif Is_Derived_Type
(Typ
) then
8350 -- For untagged types, non-stored discriminants are replaced with
8351 -- stored discriminants, which are the ones that gigi uses to
8352 -- describe the type and its components.
8354 Generate_Aggregate_For_Derived_Type
: declare
8355 procedure Prepend_Stored_Values
(T
: Entity_Id
);
8356 -- Scan the list of stored discriminants of the type, and add
8357 -- their values to the aggregate being built.
8359 ---------------------------
8360 -- Prepend_Stored_Values --
8361 ---------------------------
8363 procedure Prepend_Stored_Values
(T
: Entity_Id
) is
8365 First_Comp
: Node_Id
:= Empty
;
8368 Discr
:= First_Stored_Discriminant
(T
);
8369 while Present
(Discr
) loop
8371 Make_Component_Association
(Loc
,
8372 Choices
=> New_List
(
8373 New_Occurrence_Of
(Discr
, Loc
)),
8376 (Get_Discriminant_Value
8379 Discriminant_Constraint
(Typ
))));
8381 if No
(First_Comp
) then
8382 Prepend_To
(Component_Associations
(N
), New_Comp
);
8384 Insert_After
(First_Comp
, New_Comp
);
8387 First_Comp
:= New_Comp
;
8388 Next_Stored_Discriminant
(Discr
);
8390 end Prepend_Stored_Values
;
8394 Constraints
: constant List_Id
:= New_List
;
8398 Num_Disc
: Nat
:= 0;
8399 Num_Stor
: Nat
:= 0;
8401 -- Start of processing for Generate_Aggregate_For_Derived_Type
8404 -- Remove the associations for the discriminant of derived type
8407 First_Comp
: Node_Id
;
8410 First_Comp
:= First
(Component_Associations
(N
));
8411 while Present
(First_Comp
) loop
8415 if Ekind
(Entity
(First
(Choices
(Comp
)))) =
8419 Num_Disc
:= Num_Disc
+ 1;
8424 -- Insert stored discriminant associations in the correct
8425 -- order. If there are more stored discriminants than new
8426 -- discriminants, there is at least one new discriminant that
8427 -- constrains more than one of the stored discriminants. In
8428 -- this case we need to construct a proper subtype of the
8429 -- parent type, in order to supply values to all the
8430 -- components. Otherwise there is one-one correspondence
8431 -- between the constraints and the stored discriminants.
8433 Discr
:= First_Stored_Discriminant
(Base_Type
(Typ
));
8434 while Present
(Discr
) loop
8435 Num_Stor
:= Num_Stor
+ 1;
8436 Next_Stored_Discriminant
(Discr
);
8439 -- Case of more stored discriminants than new discriminants
8441 if Num_Stor
> Num_Disc
then
8443 -- Create a proper subtype of the parent type, which is the
8444 -- proper implementation type for the aggregate, and convert
8445 -- it to the intended target type.
8447 Discr
:= First_Stored_Discriminant
(Base_Type
(Typ
));
8448 while Present
(Discr
) loop
8451 (Get_Discriminant_Value
8454 Discriminant_Constraint
(Typ
)));
8456 Append
(New_Comp
, Constraints
);
8457 Next_Stored_Discriminant
(Discr
);
8461 Make_Subtype_Declaration
(Loc
,
8462 Defining_Identifier
=> Make_Temporary
(Loc
, 'T'),
8463 Subtype_Indication
=>
8464 Make_Subtype_Indication
(Loc
,
8466 New_Occurrence_Of
(Etype
(Base_Type
(Typ
)), Loc
),
8468 Make_Index_Or_Discriminant_Constraint
8469 (Loc
, Constraints
)));
8471 Insert_Action
(N
, Decl
);
8472 Prepend_Stored_Values
(Base_Type
(Typ
));
8474 Set_Etype
(N
, Defining_Identifier
(Decl
));
8477 Rewrite
(N
, Unchecked_Convert_To
(Typ
, N
));
8480 -- Case where we do not have fewer new discriminants than
8481 -- stored discriminants, so in this case we can simply use the
8482 -- stored discriminants of the subtype.
8485 Prepend_Stored_Values
(Typ
);
8487 end Generate_Aggregate_For_Derived_Type
;
8490 if Is_Tagged_Type
(Typ
) then
8492 -- In the tagged case, _parent and _tag component must be created
8494 -- Reset Null_Present unconditionally. Tagged records always have
8495 -- at least one field (the tag or the parent).
8497 Set_Null_Record_Present
(N
, False);
8499 -- When the current aggregate comes from the expansion of an
8500 -- extension aggregate, the parent expr is replaced by an
8501 -- aggregate formed by selected components of this expr.
8503 if Present
(Parent_Expr
) and then Is_Empty_List
(Comps
) then
8504 Comp
:= First_Component_Or_Discriminant
(Typ
);
8505 while Present
(Comp
) loop
8507 -- Skip all expander-generated components
8509 if not Comes_From_Source
(Original_Record_Component
(Comp
))
8515 Make_Selected_Component
(Loc
,
8517 Unchecked_Convert_To
(Typ
,
8518 Duplicate_Subexpr
(Parent_Expr
, True)),
8519 Selector_Name
=> New_Occurrence_Of
(Comp
, Loc
));
8522 Make_Component_Association
(Loc
,
8523 Choices
=> New_List
(
8524 New_Occurrence_Of
(Comp
, Loc
)),
8525 Expression
=> New_Comp
));
8527 Analyze_And_Resolve
(New_Comp
, Etype
(Comp
));
8530 Next_Component_Or_Discriminant
(Comp
);
8534 -- Compute the value for the Tag now, if the type is a root it
8535 -- will be included in the aggregate right away, otherwise it will
8536 -- be propagated to the parent aggregate.
8538 if Present
(Orig_Tag
) then
8539 Tag_Value
:= Orig_Tag
;
8541 elsif not Tagged_Type_Expansion
then
8547 (Node
(First_Elmt
(Access_Disp_Table
(Typ
))), Loc
);
8550 -- For a derived type, an aggregate for the parent is formed with
8551 -- all the inherited components.
8553 if Is_Derived_Type
(Typ
) then
8555 First_Comp
: Node_Id
;
8556 Parent_Comps
: List_Id
;
8557 Parent_Aggr
: Node_Id
;
8558 Parent_Name
: Node_Id
;
8561 First_Comp
:= First
(Component_Associations
(N
));
8562 Parent_Comps
:= New_List
;
8564 -- First skip the discriminants
8566 while Present
(First_Comp
)
8567 and then Ekind
(Entity
(First
(Choices
(First_Comp
))))
8573 -- Then remove the inherited component association from the
8574 -- aggregate and store them in the parent aggregate
8576 while Present
(First_Comp
)
8578 Scope
(Original_Record_Component
8579 (Entity
(First
(Choices
(First_Comp
))))) /=
8585 Append
(Comp
, Parent_Comps
);
8589 Make_Aggregate
(Loc
,
8590 Component_Associations
=> Parent_Comps
);
8591 Set_Etype
(Parent_Aggr
, Etype
(Base_Type
(Typ
)));
8593 -- Find the _parent component
8595 Comp
:= First_Component
(Typ
);
8596 while Chars
(Comp
) /= Name_uParent
loop
8597 Next_Component
(Comp
);
8600 Parent_Name
:= New_Occurrence_Of
(Comp
, Loc
);
8602 -- Insert the parent aggregate
8604 Prepend_To
(Component_Associations
(N
),
8605 Make_Component_Association
(Loc
,
8606 Choices
=> New_List
(Parent_Name
),
8607 Expression
=> Parent_Aggr
));
8609 -- Expand recursively the parent propagating the right Tag
8611 Expand_Record_Aggregate
8612 (Parent_Aggr
, Tag_Value
, Parent_Expr
);
8614 -- The ancestor part may be a nested aggregate that has
8615 -- delayed expansion: recheck now.
8617 if not Component_OK_For_Backend
then
8618 Convert_To_Assignments
(N
, Typ
);
8622 -- For a root type, the tag component is added (unless compiling
8623 -- for the VMs, where tags are implicit).
8625 elsif Tagged_Type_Expansion
then
8627 Tag_Name
: constant Node_Id
:=
8629 (First_Tag_Component
(Typ
), Loc
);
8630 Typ_Tag
: constant Entity_Id
:= RTE
(RE_Tag
);
8631 Conv_Node
: constant Node_Id
:=
8632 Unchecked_Convert_To
(Typ_Tag
, Tag_Value
);
8635 Set_Etype
(Conv_Node
, Typ_Tag
);
8636 Prepend_To
(Component_Associations
(N
),
8637 Make_Component_Association
(Loc
,
8638 Choices
=> New_List
(Tag_Name
),
8639 Expression
=> Conv_Node
));
8643 end Build_Back_End_Aggregate
;
8645 ----------------------------------------
8646 -- Compile_Time_Known_Composite_Value --
8647 ----------------------------------------
8649 function Compile_Time_Known_Composite_Value
8650 (N
: Node_Id
) return Boolean
8653 -- If we have an entity name, then see if it is the name of a
8654 -- constant and if so, test the corresponding constant value.
8656 if Is_Entity_Name
(N
) then
8658 E
: constant Entity_Id
:= Entity
(N
);
8661 if Ekind
(E
) /= E_Constant
then
8664 V
:= Constant_Value
(E
);
8666 and then Compile_Time_Known_Composite_Value
(V
);
8670 -- We have a value, see if it is compile time known
8673 if Nkind
(N
) = N_Aggregate
then
8674 return Compile_Time_Known_Aggregate
(N
);
8677 -- All other types of values are not known at compile time
8682 end Compile_Time_Known_Composite_Value
;
8684 ------------------------------
8685 -- Component_OK_For_Backend --
8686 ------------------------------
8688 function Component_OK_For_Backend
return Boolean is
8694 while Present
(C
) loop
8696 -- If the component has box initialization, expansion is needed
8697 -- and component is not ready for backend.
8699 if Box_Present
(C
) then
8703 if Nkind
(Expression
(C
)) = N_Qualified_Expression
then
8704 Expr_Q
:= Expression
(Expression
(C
));
8706 Expr_Q
:= Expression
(C
);
8709 -- Return False for array components whose bounds raise
8710 -- constraint error.
8713 Comp
: constant Entity_Id
:= First
(Choices
(C
));
8717 if Present
(Etype
(Comp
))
8718 and then Is_Array_Type
(Etype
(Comp
))
8720 Indx
:= First_Index
(Etype
(Comp
));
8721 while Present
(Indx
) loop
8722 if Nkind
(Type_Low_Bound
(Etype
(Indx
))) =
8723 N_Raise_Constraint_Error
8724 or else Nkind
(Type_High_Bound
(Etype
(Indx
))) =
8725 N_Raise_Constraint_Error
8735 -- Return False if the aggregate has any associations for tagged
8736 -- components that may require tag adjustment.
8738 -- These are cases where the source expression may have a tag that
8739 -- could differ from the component tag (e.g., can occur for type
8740 -- conversions and formal parameters). (Tag adjustment not needed
8741 -- if Tagged_Type_Expansion because object tags are implicit in
8744 if Is_Tagged_Type
(Etype
(Expr_Q
))
8746 (Nkind
(Expr_Q
) = N_Type_Conversion
8748 (Is_Entity_Name
(Expr_Q
)
8749 and then Is_Formal
(Entity
(Expr_Q
))))
8750 and then Tagged_Type_Expansion
8752 Static_Components
:= False;
8755 elsif Is_Delayed_Aggregate
(Expr_Q
) then
8756 Static_Components
:= False;
8759 elsif Nkind
(Expr_Q
) = N_Quantified_Expression
then
8760 Static_Components
:= False;
8763 elsif Possible_Bit_Aligned_Component
(Expr_Q
) then
8764 Static_Components
:= False;
8767 elsif Modify_Tree_For_C
8768 and then Nkind
(C
) = N_Component_Association
8769 and then Has_Per_Object_Constraint
(Choices
(C
))
8771 Static_Components
:= False;
8774 elsif Modify_Tree_For_C
8775 and then Nkind
(Expr_Q
) = N_Identifier
8776 and then Is_Array_Type
(Etype
(Expr_Q
))
8778 Static_Components
:= False;
8781 elsif Modify_Tree_For_C
8782 and then Nkind
(Expr_Q
) = N_Type_Conversion
8783 and then Is_Array_Type
(Etype
(Expr_Q
))
8785 Static_Components
:= False;
8789 if Is_Elementary_Type
(Etype
(Expr_Q
)) then
8790 if not Compile_Time_Known_Value
(Expr_Q
) then
8791 Static_Components
:= False;
8794 elsif not Compile_Time_Known_Composite_Value
(Expr_Q
) then
8795 Static_Components
:= False;
8797 if Is_Private_Type
(Etype
(Expr_Q
))
8798 and then Has_Discriminants
(Etype
(Expr_Q
))
8808 end Component_OK_For_Backend
;
8810 -------------------------------
8811 -- Has_Per_Object_Constraint --
8812 -------------------------------
8814 function Has_Per_Object_Constraint
(L
: List_Id
) return Boolean is
8815 N
: Node_Id
:= First
(L
);
8817 while Present
(N
) loop
8818 if Is_Entity_Name
(N
)
8819 and then Present
(Entity
(N
))
8820 and then Has_Per_Object_Constraint
(Entity
(N
))
8829 end Has_Per_Object_Constraint
;
8831 -----------------------------------
8832 -- Has_Visible_Private_Ancestor --
8833 -----------------------------------
8835 function Has_Visible_Private_Ancestor
(Id
: E
) return Boolean is
8836 R
: constant Entity_Id
:= Root_Type
(Id
);
8837 T1
: Entity_Id
:= Id
;
8841 if Is_Private_Type
(T1
) then
8851 end Has_Visible_Private_Ancestor
;
8853 -------------------------
8854 -- Top_Level_Aggregate --
8855 -------------------------
8857 function Top_Level_Aggregate
(N
: Node_Id
) return Node_Id
is
8862 while Present
(Parent
(Aggr
))
8863 and then Nkind
(Parent
(Aggr
)) in
8864 N_Aggregate | N_Component_Association
8866 Aggr
:= Parent
(Aggr
);
8870 end Top_Level_Aggregate
;
8874 Top_Level_Aggr
: constant Node_Id
:= Top_Level_Aggregate
(N
);
8876 -- Start of processing for Expand_Record_Aggregate
8879 -- No special management required for aggregates used to initialize
8880 -- statically allocated dispatch tables
8882 if Is_Static_Dispatch_Table_Aggregate
(N
) then
8885 -- Case pattern aggregates need to remain as aggregates
8887 elsif Is_Case_Choice_Pattern
(N
) then
8891 -- If the pragma Aggregate_Individually_Assign is set, always convert to
8894 if Aggregate_Individually_Assign
then
8895 Convert_To_Assignments
(N
, Typ
);
8897 -- Ada 2005 (AI-318-2): We need to convert to assignments if components
8898 -- are build-in-place function calls. The assignments will each turn
8899 -- into a build-in-place function call. If components are all static,
8900 -- we can pass the aggregate to the back end regardless of limitedness.
8902 -- Extension aggregates, aggregates in extended return statements, and
8903 -- aggregates for C++ imported types must be expanded.
8905 elsif Ada_Version
>= Ada_2005
and then Is_Limited_View
(Typ
) then
8906 if Nkind
(Parent
(N
)) not in
8907 N_Component_Association | N_Object_Declaration
8909 Convert_To_Assignments
(N
, Typ
);
8911 elsif Nkind
(N
) = N_Extension_Aggregate
8912 or else Convention
(Typ
) = Convention_CPP
8914 Convert_To_Assignments
(N
, Typ
);
8916 elsif not Size_Known_At_Compile_Time
(Typ
)
8917 or else not Component_OK_For_Backend
8918 or else not Static_Components
8920 Convert_To_Assignments
(N
, Typ
);
8922 -- In all other cases, build a proper aggregate to be handled by
8926 Build_Back_End_Aggregate
;
8929 -- Gigi doesn't properly handle temporaries of variable size so we
8930 -- generate it in the front-end
8932 elsif not Size_Known_At_Compile_Time
(Typ
)
8933 and then Tagged_Type_Expansion
8935 Convert_To_Assignments
(N
, Typ
);
8937 -- An aggregate used to initialize a controlled object must be turned
8938 -- into component assignments as the components themselves may require
8939 -- finalization actions such as adjustment.
8941 elsif Needs_Finalization
(Typ
) then
8942 Convert_To_Assignments
(N
, Typ
);
8944 -- Ada 2005 (AI-287): In case of default initialized components we
8945 -- convert the aggregate into assignments.
8947 elsif Has_Default_Init_Comps
(N
) then
8948 Convert_To_Assignments
(N
, Typ
);
8952 elsif not Component_OK_For_Backend
then
8953 Convert_To_Assignments
(N
, Typ
);
8955 -- If an ancestor is private, some components are not inherited and we
8956 -- cannot expand into a record aggregate.
8958 elsif Has_Visible_Private_Ancestor
(Typ
) then
8959 Convert_To_Assignments
(N
, Typ
);
8961 -- ??? The following was done to compile fxacc00.ads in the ACVCs. Gigi
8962 -- is not able to handle the aggregate for Late_Request.
8964 elsif Is_Tagged_Type
(Typ
) and then Has_Discriminants
(Typ
) then
8965 Convert_To_Assignments
(N
, Typ
);
8967 -- If the tagged types covers interface types we need to initialize all
8968 -- hidden components containing pointers to secondary dispatch tables.
8970 elsif Is_Tagged_Type
(Typ
) and then Has_Interfaces
(Typ
) then
8971 Convert_To_Assignments
(N
, Typ
);
8973 -- If some components are mutable, the size of the aggregate component
8974 -- may be distinct from the default size of the type component, so
8975 -- we need to expand to insure that the back-end copies the proper
8976 -- size of the data. However, if the aggregate is the initial value of
8977 -- a constant, the target is immutable and might be built statically
8978 -- if components are appropriate.
8980 elsif Has_Mutable_Components
(Typ
)
8982 (Nkind
(Parent
(Top_Level_Aggr
)) /= N_Object_Declaration
8983 or else not Constant_Present
(Parent
(Top_Level_Aggr
))
8984 or else not Static_Components
)
8986 Convert_To_Assignments
(N
, Typ
);
8988 -- If the type involved has bit aligned components, then we are not sure
8989 -- that the back end can handle this case correctly.
8991 elsif Type_May_Have_Bit_Aligned_Components
(Typ
) then
8992 Convert_To_Assignments
(N
, Typ
);
8994 -- When generating C, only generate an aggregate when declaring objects
8995 -- since C does not support aggregates in e.g. assignment statements.
8997 elsif Modify_Tree_For_C
and then not Is_CCG_Supported_Aggregate
(N
) then
8998 Convert_To_Assignments
(N
, Typ
);
9000 -- In all other cases, build a proper aggregate to be handled by gigi
9003 Build_Back_End_Aggregate
;
9005 end Expand_Record_Aggregate
;
9007 ---------------------
9008 -- Get_Base_Object --
9009 ---------------------
9011 function Get_Base_Object
(N
: Node_Id
) return Entity_Id
is
9015 R
:= Get_Referenced_Object
(N
);
9017 while Nkind
(R
) in N_Indexed_Component | N_Selected_Component | N_Slice
9019 R
:= Get_Referenced_Object
(Prefix
(R
));
9022 if Is_Entity_Name
(R
) and then Is_Object
(Entity
(R
)) then
9027 end Get_Base_Object
;
9029 ----------------------------
9030 -- Has_Default_Init_Comps --
9031 ----------------------------
9033 function Has_Default_Init_Comps
(N
: Node_Id
) return Boolean is
9036 -- Component association and expression, respectively
9039 pragma Assert
(Nkind
(N
) in N_Aggregate | N_Extension_Aggregate
);
9041 if Has_Self_Reference
(N
) then
9045 Assoc
:= First
(Component_Associations
(N
));
9046 while Present
(Assoc
) loop
9047 -- Each component association has either a box or an expression
9049 pragma Assert
(Box_Present
(Assoc
) xor Present
(Expression
(Assoc
)));
9051 -- Check if any direct component has default initialized components
9053 if Box_Present
(Assoc
) then
9056 -- Recursive call in case of aggregate expression
9059 Expr
:= Expression
(Assoc
);
9061 if Nkind
(Expr
) in N_Aggregate | N_Extension_Aggregate
9062 and then Has_Default_Init_Comps
(Expr
)
9072 end Has_Default_Init_Comps
;
9074 ----------------------------------------
9075 -- Is_Build_In_Place_Aggregate_Return --
9076 ----------------------------------------
9078 function Is_Build_In_Place_Aggregate_Return
(N
: Node_Id
) return Boolean is
9079 P
: Node_Id
:= Parent
(N
);
9082 while Nkind
(P
) = N_Qualified_Expression
loop
9086 if Nkind
(P
) = N_Simple_Return_Statement
then
9089 elsif Nkind
(Parent
(P
)) = N_Extended_Return_Statement
then
9097 Is_Build_In_Place_Function
9098 (Return_Applies_To
(Return_Statement_Entity
(P
)));
9099 end Is_Build_In_Place_Aggregate_Return
;
9101 --------------------------
9102 -- Is_Delayed_Aggregate --
9103 --------------------------
9105 function Is_Delayed_Aggregate
(N
: Node_Id
) return Boolean is
9106 Node
: Node_Id
:= N
;
9107 Kind
: Node_Kind
:= Nkind
(Node
);
9110 if Kind
= N_Qualified_Expression
then
9111 Node
:= Expression
(Node
);
9112 Kind
:= Nkind
(Node
);
9115 return Kind
in N_Aggregate | N_Extension_Aggregate
9116 and then Expansion_Delayed
(Node
);
9117 end Is_Delayed_Aggregate
;
9119 --------------------------------
9120 -- Is_CCG_Supported_Aggregate --
9121 --------------------------------
9123 function Is_CCG_Supported_Aggregate
9124 (N
: Node_Id
) return Boolean
9126 P
: Node_Id
:= Parent
(N
);
9129 -- Aggregates are not supported for nonstandard rep clauses, since they
9130 -- may lead to extra padding fields in CCG.
9132 if Is_Record_Type
(Etype
(N
))
9133 and then Has_Non_Standard_Rep
(Etype
(N
))
9138 while Present
(P
) and then Nkind
(P
) = N_Aggregate
loop
9142 -- Check cases where aggregates are supported by the CCG backend
9144 if Nkind
(P
) = N_Object_Declaration
then
9146 P_Typ
: constant Entity_Id
:= Etype
(Defining_Identifier
(P
));
9149 if Is_Record_Type
(P_Typ
) then
9152 return Compile_Time_Known_Bounds
(P_Typ
);
9156 elsif Nkind
(P
) = N_Qualified_Expression
then
9157 if Nkind
(Parent
(P
)) = N_Object_Declaration
then
9159 P_Typ
: constant Entity_Id
:=
9160 Etype
(Defining_Identifier
(Parent
(P
)));
9162 if Is_Record_Type
(P_Typ
) then
9165 return Compile_Time_Known_Bounds
(P_Typ
);
9169 elsif Nkind
(Parent
(P
)) = N_Allocator
then
9175 end Is_CCG_Supported_Aggregate
;
9177 ----------------------------------------
9178 -- Is_Static_Dispatch_Table_Aggregate --
9179 ----------------------------------------
9181 function Is_Static_Dispatch_Table_Aggregate
(N
: Node_Id
) return Boolean is
9182 Typ
: constant Entity_Id
:= Base_Type
(Etype
(N
));
9185 return Building_Static_Dispatch_Tables
9186 and then Tagged_Type_Expansion
9188 -- Avoid circularity when rebuilding the compiler
9190 and then not Is_RTU
(Cunit_Entity
(Get_Source_Unit
(N
)), Ada_Tags
)
9191 and then (Is_RTE
(Typ
, RE_Dispatch_Table_Wrapper
)
9193 Is_RTE
(Typ
, RE_Address_Array
)
9195 Is_RTE
(Typ
, RE_Type_Specific_Data
)
9197 Is_RTE
(Typ
, RE_Tag_Table
)
9199 Is_RTE
(Typ
, RE_Object_Specific_Data
)
9201 Is_RTE
(Typ
, RE_Interface_Data
)
9203 Is_RTE
(Typ
, RE_Interfaces_Array
)
9205 Is_RTE
(Typ
, RE_Interface_Data_Element
));
9206 end Is_Static_Dispatch_Table_Aggregate
;
9208 -----------------------------
9209 -- Is_Two_Dim_Packed_Array --
9210 -----------------------------
9212 function Is_Two_Dim_Packed_Array
(Typ
: Entity_Id
) return Boolean is
9213 C
: constant Uint
:= Component_Size
(Typ
);
9215 return Number_Dimensions
(Typ
) = 2
9216 and then Is_Bit_Packed_Array
(Typ
)
9217 and then C
in Uint_1 | Uint_2 | Uint_4
; -- False if No_Uint
9218 end Is_Two_Dim_Packed_Array
;
9220 --------------------
9221 -- Late_Expansion --
9222 --------------------
9224 function Late_Expansion
9227 Target
: Node_Id
) return List_Id
9229 Aggr_Code
: List_Id
;
9233 if Is_Array_Type
(Typ
) then
9234 -- If the assignment can be done directly by the back end, then
9235 -- reset Set_Expansion_Delayed and do not expand further.
9237 if not CodePeer_Mode
9238 and then not Modify_Tree_For_C
9239 and then not Possible_Bit_Aligned_Component
(Target
)
9240 and then not Is_Possibly_Unaligned_Slice
(Target
)
9241 and then Aggr_Assignment_OK_For_Backend
(N
)
9243 New_Aggr
:= New_Copy_Tree
(N
);
9244 Set_Expansion_Delayed
(New_Aggr
, False);
9248 Make_OK_Assignment_Statement
(Sloc
(New_Aggr
),
9250 Expression
=> New_Aggr
));
9252 -- Or else, generate component assignments to it
9256 Build_Array_Aggr_Code
9258 Ctype
=> Component_Type
(Typ
),
9259 Index
=> First_Index
(Typ
),
9261 Scalar_Comp
=> Is_Scalar_Type
(Component_Type
(Typ
)),
9262 Indexes
=> No_List
);
9265 -- Directly or indirectly (e.g. access protected procedure) a record
9268 Aggr_Code
:= Build_Record_Aggr_Code
(N
, Typ
, Target
);
9271 -- Save the last assignment statement associated with the aggregate
9272 -- when building a controlled object. This reference is utilized by
9273 -- the finalization machinery when marking an object as successfully
9276 if Needs_Finalization
(Typ
)
9277 and then Is_Entity_Name
(Target
)
9278 and then Present
(Entity
(Target
))
9279 and then Ekind
(Entity
(Target
)) in E_Constant | E_Variable
9281 Set_Last_Aggregate_Assignment
(Entity
(Target
), Last
(Aggr_Code
));
9287 ----------------------------------
9288 -- Make_OK_Assignment_Statement --
9289 ----------------------------------
9291 function Make_OK_Assignment_Statement
9294 Expression
: Node_Id
) return Node_Id
9297 Set_Assignment_OK
(Name
);
9298 return Make_Assignment_Statement
(Sloc
, Name
, Expression
);
9299 end Make_OK_Assignment_Statement
;
9301 ------------------------
9302 -- Max_Aggregate_Size --
9303 ------------------------
9305 function Max_Aggregate_Size
9307 Default_Size
: Nat
:= 5000) return Nat
9309 function Use_Small_Size
(N
: Node_Id
) return Boolean;
9310 -- True if we should return a very small size, which means large
9311 -- aggregates will be implemented as a loop when possible (potentially
9312 -- transformed to memset calls).
9314 function Aggr_Context
(N
: Node_Id
) return Node_Id
;
9315 -- Return the context in which the aggregate appears, not counting
9316 -- qualified expressions and similar.
9322 function Aggr_Context
(N
: Node_Id
) return Node_Id
is
9323 Result
: Node_Id
:= Parent
(N
);
9325 if Nkind
(Result
) in N_Qualified_Expression
9327 | N_Unchecked_Type_Conversion
9330 | N_Component_Association
9333 Result
:= Aggr_Context
(Result
);
9339 --------------------
9340 -- Use_Small_Size --
9341 --------------------
9343 function Use_Small_Size
(N
: Node_Id
) return Boolean is
9344 C
: constant Node_Id
:= Aggr_Context
(N
);
9345 -- The decision depends on the context in which the aggregate occurs,
9346 -- and for variable declarations, whether we are nested inside a
9350 -- True for assignment statements and similar
9352 when N_Assignment_Statement
9353 | N_Simple_Return_Statement
9355 | N_Attribute_Reference
9359 -- True for nested variable declarations. False for library level
9360 -- variables, and for constants (whether or not nested).
9362 when N_Object_Declaration
=>
9363 return not Constant_Present
(C
)
9364 and then Is_Subprogram
(Current_Scope
);
9366 -- False for all other contexts
9375 Typ
: constant Entity_Id
:= Etype
(N
);
9377 -- Start of processing for Max_Aggregate_Size
9380 -- We use a small limit in CodePeer mode where we favor loops instead of
9381 -- thousands of single assignments (from large aggregates).
9383 -- We also increase the limit to 2**24 (about 16 million) if
9384 -- Restrictions (No_Elaboration_Code) or Restrictions
9385 -- (No_Implicit_Loops) is specified, since in either case we are at risk
9386 -- of declaring the program illegal because of this limit. We also
9387 -- increase the limit when Static_Elaboration_Desired, given that this
9388 -- means that objects are intended to be placed in data memory.
9390 -- Same if the aggregate is for a packed two-dimensional array, because
9391 -- if components are static it is much more efficient to construct a
9392 -- one-dimensional equivalent array with static components.
9394 if CodePeer_Mode
then
9396 elsif Restriction_Active
(No_Elaboration_Code
)
9397 or else Restriction_Active
(No_Implicit_Loops
)
9398 or else Is_Two_Dim_Packed_Array
(Typ
)
9399 or else (Ekind
(Current_Scope
) = E_Package
9400 and then Static_Elaboration_Desired
(Current_Scope
))
9403 elsif Use_Small_Size
(N
) then
9407 return Default_Size
;
9408 end Max_Aggregate_Size
;
9410 -----------------------
9411 -- Number_Of_Choices --
9412 -----------------------
9414 function Number_Of_Choices
(N
: Node_Id
) return Nat
is
9418 Nb_Choices
: Nat
:= 0;
9421 if Present
(Expressions
(N
)) then
9425 Assoc
:= First
(Component_Associations
(N
));
9426 while Present
(Assoc
) loop
9427 Choice
:= First
(Choice_List
(Assoc
));
9428 while Present
(Choice
) loop
9429 if Nkind
(Choice
) /= N_Others_Choice
then
9430 Nb_Choices
:= Nb_Choices
+ 1;
9440 end Number_Of_Choices
;
9442 ------------------------------------
9443 -- Packed_Array_Aggregate_Handled --
9444 ------------------------------------
9446 -- The current version of this procedure will handle at compile time
9447 -- any array aggregate that meets these conditions:
9449 -- One and two dimensional, bit packed
9450 -- Underlying packed type is modular type
9451 -- Bounds are within 32-bit Int range
9452 -- All bounds and values are static
9454 -- Note: for now, in the 2-D case, we only handle component sizes of
9455 -- 1, 2, 4 (cases where an integral number of elements occupies a byte).
9457 function Packed_Array_Aggregate_Handled
(N
: Node_Id
) return Boolean is
9458 Loc
: constant Source_Ptr
:= Sloc
(N
);
9459 Typ
: constant Entity_Id
:= Etype
(N
);
9460 Ctyp
: constant Entity_Id
:= Component_Type
(Typ
);
9462 Not_Handled
: exception;
9463 -- Exception raised if this aggregate cannot be handled
9466 -- Handle one- or two dimensional bit packed array
9468 if not Is_Bit_Packed_Array
(Typ
)
9469 or else Number_Dimensions
(Typ
) > 2
9474 -- If two-dimensional, check whether it can be folded, and transformed
9475 -- into a one-dimensional aggregate for the Packed_Array_Impl_Type of
9476 -- the original type.
9478 if Number_Dimensions
(Typ
) = 2 then
9479 return Two_Dim_Packed_Array_Handled
(N
);
9482 if not Is_Modular_Integer_Type
(Packed_Array_Impl_Type
(Typ
)) then
9486 if not Is_Scalar_Type
(Ctyp
) then
9491 Csiz
: constant Nat
:= UI_To_Int
(Component_Size
(Typ
));
9493 function Get_Component_Val
(N
: Node_Id
) return Uint
;
9494 -- Given a expression value N of the component type Ctyp, returns a
9495 -- value of Csiz (component size) bits representing this value. If
9496 -- the value is nonstatic or any other reason exists why the value
9497 -- cannot be returned, then Not_Handled is raised.
9499 -----------------------
9500 -- Get_Component_Val --
9501 -----------------------
9503 function Get_Component_Val
(N
: Node_Id
) return Uint
is
9507 -- We have to analyze the expression here before doing any further
9508 -- processing here. The analysis of such expressions is deferred
9509 -- till expansion to prevent some problems of premature analysis.
9511 Analyze_And_Resolve
(N
, Ctyp
);
9513 -- Must have a compile time value. String literals have to be
9514 -- converted into temporaries as well, because they cannot easily
9515 -- be converted into their bit representation.
9517 if not Compile_Time_Known_Value
(N
)
9518 or else Nkind
(N
) = N_String_Literal
9523 Val
:= Expr_Rep_Value
(N
);
9525 -- Adjust for bias, and strip proper number of bits
9527 if Has_Biased_Representation
(Ctyp
) then
9528 Val
:= Val
- Expr_Value
(Type_Low_Bound
(Ctyp
));
9531 return Val
mod Uint_2
** Csiz
;
9532 end Get_Component_Val
;
9534 Bounds
: constant Range_Nodes
:= Get_Index_Bounds
(First_Index
(Typ
));
9536 -- Here we know we have a one dimensional bit packed array
9539 -- Cannot do anything if bounds are dynamic
9541 if not (Compile_Time_Known_Value
(Bounds
.First
)
9543 Compile_Time_Known_Value
(Bounds
.Last
))
9549 Bounds_Vals
: Range_Values
;
9550 -- Compile-time known values of bounds
9552 -- Or are silly out of range of int bounds
9554 Bounds_Vals
.First
:= Expr_Value
(Bounds
.First
);
9555 Bounds_Vals
.Last
:= Expr_Value
(Bounds
.Last
);
9557 if not UI_Is_In_Int_Range
(Bounds_Vals
.First
)
9559 not UI_Is_In_Int_Range
(Bounds_Vals
.Last
)
9564 -- At this stage we have a suitable aggregate for handling at
9565 -- compile time. The only remaining checks are that the values of
9566 -- expressions in the aggregate are compile-time known (checks are
9567 -- performed by Get_Component_Val), and that any subtypes or
9568 -- ranges are statically known.
9570 -- If the aggregate is not fully positional at this stage, then
9571 -- convert it to positional form. Either this will fail, in which
9572 -- case we can do nothing, or it will succeed, in which case we
9573 -- have succeeded in handling the aggregate and transforming it
9574 -- into a modular value, or it will stay an aggregate, in which
9575 -- case we have failed to create a packed value for it.
9577 if Present
(Component_Associations
(N
)) then
9578 Convert_To_Positional
(N
, Handle_Bit_Packed
=> True);
9579 return Nkind
(N
) /= N_Aggregate
;
9582 -- Otherwise we are all positional, so convert to proper value
9585 Len
: constant Nat
:=
9586 Int
'Max (0, UI_To_Int
(Bounds_Vals
.Last
) -
9587 UI_To_Int
(Bounds_Vals
.First
) + 1);
9588 -- The length of the array (number of elements)
9590 Aggregate_Val
: Uint
;
9591 -- Value of aggregate. The value is set in the low order bits
9592 -- of this value. For the little-endian case, the values are
9593 -- stored from low-order to high-order and for the big-endian
9594 -- case the values are stored from high order to low order.
9595 -- Note that gigi will take care of the conversions to left
9596 -- justify the value in the big endian case (because of left
9597 -- justified modular type processing), so we do not have to
9598 -- worry about that here.
9601 -- Integer literal for resulting constructed value
9604 -- Shift count from low order for next value
9607 -- Shift increment for loop
9610 -- Next expression from positional parameters of aggregate
9612 Left_Justified
: Boolean;
9613 -- Set True if we are filling the high order bits of the target
9614 -- value (i.e. the value is left justified).
9617 -- For little endian, we fill up the low order bits of the
9618 -- target value. For big endian we fill up the high order bits
9619 -- of the target value (which is a left justified modular
9622 Left_Justified
:= Bytes_Big_Endian
;
9624 -- Switch justification if using -gnatd8
9626 if Debug_Flag_8
then
9627 Left_Justified
:= not Left_Justified
;
9630 -- Switch justfification if reverse storage order
9632 if Reverse_Storage_Order
(Base_Type
(Typ
)) then
9633 Left_Justified
:= not Left_Justified
;
9636 if Left_Justified
then
9637 Shift
:= Csiz
* (Len
- 1);
9644 -- Loop to set the values
9647 Aggregate_Val
:= Uint_0
;
9649 Expr
:= First
(Expressions
(N
));
9650 Aggregate_Val
:= Get_Component_Val
(Expr
) * Uint_2
** Shift
;
9652 for J
in 2 .. Len
loop
9653 Shift
:= Shift
+ Incr
;
9657 Get_Component_Val
(Expr
) * Uint_2
** Shift
;
9661 -- Now we can rewrite with the proper value
9663 Lit
:= Make_Integer_Literal
(Loc
, Intval
=> Aggregate_Val
);
9664 Set_Print_In_Hex
(Lit
);
9666 -- Construct the expression using this literal. Note that it
9667 -- is important to qualify the literal with its proper modular
9668 -- type since universal integer does not have the required
9669 -- range and also this is a left justified modular type,
9670 -- which is important in the big-endian case.
9673 Unchecked_Convert_To
(Typ
,
9674 Make_Qualified_Expression
(Loc
,
9676 New_Occurrence_Of
(Packed_Array_Impl_Type
(Typ
), Loc
),
9677 Expression
=> Lit
)));
9679 Analyze_And_Resolve
(N
, Typ
);
9688 end Packed_Array_Aggregate_Handled
;
9690 ----------------------------
9691 -- Has_Mutable_Components --
9692 ----------------------------
9694 function Has_Mutable_Components
(Typ
: Entity_Id
) return Boolean is
9699 Comp
:= First_Component
(Typ
);
9700 while Present
(Comp
) loop
9701 Ctyp
:= Underlying_Type
(Etype
(Comp
));
9702 if Is_Record_Type
(Ctyp
)
9703 and then Has_Discriminants
(Ctyp
)
9704 and then not Is_Constrained
(Ctyp
)
9709 Next_Component
(Comp
);
9713 end Has_Mutable_Components
;
9715 ------------------------------
9716 -- Initialize_Discriminants --
9717 ------------------------------
9719 procedure Initialize_Discriminants
(N
: Node_Id
; Typ
: Entity_Id
) is
9720 Loc
: constant Source_Ptr
:= Sloc
(N
);
9721 Bas
: constant Entity_Id
:= Base_Type
(Typ
);
9722 Par
: constant Entity_Id
:= Etype
(Bas
);
9723 Decl
: constant Node_Id
:= Parent
(Par
);
9727 if Is_Tagged_Type
(Bas
)
9728 and then Is_Derived_Type
(Bas
)
9729 and then Has_Discriminants
(Par
)
9730 and then Has_Discriminants
(Bas
)
9731 and then Number_Discriminants
(Bas
) /= Number_Discriminants
(Par
)
9732 and then Nkind
(Decl
) = N_Full_Type_Declaration
9733 and then Nkind
(Type_Definition
(Decl
)) = N_Record_Definition
9735 Present
(Variant_Part
(Component_List
(Type_Definition
(Decl
))))
9736 and then Nkind
(N
) /= N_Extension_Aggregate
9739 -- Call init proc to set discriminants.
9740 -- There should eventually be a special procedure for this ???
9742 Ref
:= New_Occurrence_Of
(Defining_Identifier
(N
), Loc
);
9743 Insert_Actions_After
(N
,
9744 Build_Initialization_Call
(Sloc
(N
), Ref
, Typ
));
9746 end Initialize_Discriminants
;
9754 Obj_Type
: Entity_Id
;
9755 Typ
: Entity_Id
) return Boolean
9758 -- No sliding if the type of the object is not established yet, if it is
9759 -- an unconstrained type whose actual subtype comes from the aggregate,
9760 -- or if the two types are identical. If the aggregate contains only
9761 -- an Others_Clause it gets its type from the context and no sliding
9762 -- is involved either.
9764 if not Is_Array_Type
(Obj_Type
) then
9767 elsif not Is_Constrained
(Obj_Type
) then
9770 elsif Typ
= Obj_Type
then
9773 elsif Is_Others_Aggregate
(Aggr
) then
9777 -- Sliding can only occur along the first dimension
9778 -- If any the bounds of non-static sliding is required
9779 -- to force potential range checks.
9782 Bounds1
: constant Range_Nodes
:=
9783 Get_Index_Bounds
(First_Index
(Typ
));
9784 Bounds2
: constant Range_Nodes
:=
9785 Get_Index_Bounds
(First_Index
(Obj_Type
));
9788 if not Is_OK_Static_Expression
(Bounds1
.First
) or else
9789 not Is_OK_Static_Expression
(Bounds2
.First
) or else
9790 not Is_OK_Static_Expression
(Bounds1
.Last
) or else
9791 not Is_OK_Static_Expression
(Bounds2
.Last
)
9796 return Expr_Value
(Bounds1
.First
) /= Expr_Value
(Bounds2
.First
)
9798 Expr_Value
(Bounds1
.Last
) /= Expr_Value
(Bounds2
.Last
);
9804 ---------------------------------
9805 -- Process_Transient_Component --
9806 ---------------------------------
9808 procedure Process_Transient_Component
9810 Comp_Typ
: Entity_Id
;
9811 Init_Expr
: Node_Id
;
9812 Fin_Call
: out Node_Id
;
9813 Hook_Clear
: out Node_Id
;
9814 Aggr
: Node_Id
:= Empty
;
9815 Stmts
: List_Id
:= No_List
)
9817 procedure Add_Item
(Item
: Node_Id
);
9818 -- Insert arbitrary node Item into the tree depending on the values of
9825 procedure Add_Item
(Item
: Node_Id
) is
9827 if Present
(Aggr
) then
9828 Insert_Action
(Aggr
, Item
);
9830 pragma Assert
(Present
(Stmts
));
9831 Append_To
(Stmts
, Item
);
9837 Hook_Assign
: Node_Id
;
9838 Hook_Decl
: Node_Id
;
9842 Res_Typ
: Entity_Id
;
9843 Copy_Init_Expr
: constant Node_Id
:= New_Copy_Tree
(Init_Expr
);
9845 -- Start of processing for Process_Transient_Component
9848 -- Add the access type, which provides a reference to the function
9849 -- result. Generate:
9851 -- type Res_Typ is access all Comp_Typ;
9853 Res_Typ
:= Make_Temporary
(Loc
, 'A');
9854 Mutate_Ekind
(Res_Typ
, E_General_Access_Type
);
9855 Set_Directly_Designated_Type
(Res_Typ
, Comp_Typ
);
9858 (Make_Full_Type_Declaration
(Loc
,
9859 Defining_Identifier
=> Res_Typ
,
9861 Make_Access_To_Object_Definition
(Loc
,
9862 All_Present
=> True,
9863 Subtype_Indication
=> New_Occurrence_Of
(Comp_Typ
, Loc
))));
9865 -- Add the temporary which captures the result of the function call.
9868 -- Res : constant Res_Typ := Init_Expr'Reference;
9870 -- Note that this temporary is effectively a transient object because
9871 -- its lifetime is bounded by the current array or record component.
9873 Res_Id
:= Make_Temporary
(Loc
, 'R');
9874 Mutate_Ekind
(Res_Id
, E_Constant
);
9875 Set_Etype
(Res_Id
, Res_Typ
);
9877 -- Mark the transient object as successfully processed to avoid double
9880 Set_Is_Finalized_Transient
(Res_Id
);
9882 -- Signal the general finalization machinery that this transient object
9883 -- should not be considered for finalization actions because its cleanup
9884 -- will be performed by Process_Transient_Component_Completion.
9886 Set_Is_Ignored_Transient
(Res_Id
);
9889 Make_Object_Declaration
(Loc
,
9890 Defining_Identifier
=> Res_Id
,
9891 Constant_Present
=> True,
9892 Object_Definition
=> New_Occurrence_Of
(Res_Typ
, Loc
),
9894 Make_Reference
(Loc
, Copy_Init_Expr
));
9896 -- In some cases, like iterated component, the Init_Expr may have been
9897 -- analyzed in a context where all the Etype fields are not correct yet
9898 -- and a later call to Analyze is expected to set them.
9899 -- Resetting the Analyzed flag ensures this later call doesn't skip this
9902 Reset_Analyzed_Flags
(Copy_Init_Expr
);
9904 Add_Item
(Res_Decl
);
9906 -- Construct all pieces necessary to hook and finalize the transient
9909 Build_Transient_Object_Statements
9910 (Obj_Decl
=> Res_Decl
,
9911 Fin_Call
=> Fin_Call
,
9912 Hook_Assign
=> Hook_Assign
,
9913 Hook_Clear
=> Hook_Clear
,
9914 Hook_Decl
=> Hook_Decl
,
9915 Ptr_Decl
=> Ptr_Decl
);
9917 -- Add the access type which provides a reference to the transient
9918 -- result. Generate:
9920 -- type Ptr_Typ is access all Comp_Typ;
9922 Add_Item
(Ptr_Decl
);
9924 -- Add the temporary which acts as a hook to the transient result.
9927 -- Hook : Ptr_Typ := null;
9929 Add_Item
(Hook_Decl
);
9931 -- Attach the transient result to the hook. Generate:
9933 -- Hook := Ptr_Typ (Res);
9935 Add_Item
(Hook_Assign
);
9937 -- The original initialization expression now references the value of
9938 -- the temporary function result. Generate:
9943 Make_Explicit_Dereference
(Loc
,
9944 Prefix
=> New_Occurrence_Of
(Res_Id
, Loc
)));
9945 end Process_Transient_Component
;
9947 --------------------------------------------
9948 -- Process_Transient_Component_Completion --
9949 --------------------------------------------
9951 procedure Process_Transient_Component_Completion
9955 Hook_Clear
: Node_Id
;
9958 Exceptions_OK
: constant Boolean :=
9959 not Restriction_Active
(No_Exception_Propagation
);
9962 pragma Assert
(Present
(Hook_Clear
));
9964 -- Generate the following code if exception propagation is allowed:
9967 -- Abort : constant Boolean := Triggered_By_Abort;
9969 -- Abort : constant Boolean := False; -- no abort
9971 -- E : Exception_Occurrence;
9972 -- Raised : Boolean := False;
9979 -- [Deep_]Finalize (Res.all);
9983 -- if not Raised then
9985 -- Save_Occurrence (E,
9986 -- Get_Curent_Excep.all.all);
9992 -- if Raised and then not Abort then
9993 -- Raise_From_Controlled_Operation (E);
9997 if Exceptions_OK
then
9998 Abort_And_Exception
: declare
9999 Blk_Decls
: constant List_Id
:= New_List
;
10000 Blk_Stmts
: constant List_Id
:= New_List
;
10001 Fin_Stmts
: constant List_Id
:= New_List
;
10003 Fin_Data
: Finalization_Exception_Data
;
10006 -- Create the declarations of the two flags and the exception
10009 Build_Object_Declarations
(Fin_Data
, Blk_Decls
, Loc
);
10014 if Abort_Allowed
then
10015 Append_To
(Blk_Stmts
,
10016 Build_Runtime_Call
(Loc
, RE_Abort_Defer
));
10019 -- Wrap the hook clear and the finalization call in order to trap
10020 -- a potential exception.
10022 Append_To
(Fin_Stmts
, Hook_Clear
);
10024 if Present
(Fin_Call
) then
10025 Append_To
(Fin_Stmts
, Fin_Call
);
10028 Append_To
(Blk_Stmts
,
10029 Make_Block_Statement
(Loc
,
10030 Handled_Statement_Sequence
=>
10031 Make_Handled_Sequence_Of_Statements
(Loc
,
10032 Statements
=> Fin_Stmts
,
10033 Exception_Handlers
=> New_List
(
10034 Build_Exception_Handler
(Fin_Data
)))));
10039 if Abort_Allowed
then
10040 Append_To
(Blk_Stmts
,
10041 Build_Runtime_Call
(Loc
, RE_Abort_Undefer
));
10044 -- Reraise the potential exception with a proper "upgrade" to
10045 -- Program_Error if needed.
10047 Append_To
(Blk_Stmts
, Build_Raise_Statement
(Fin_Data
));
10049 -- Wrap everything in a block
10052 Make_Block_Statement
(Loc
,
10053 Declarations
=> Blk_Decls
,
10054 Handled_Statement_Sequence
=>
10055 Make_Handled_Sequence_Of_Statements
(Loc
,
10056 Statements
=> Blk_Stmts
)));
10057 end Abort_And_Exception
;
10059 -- Generate the following code if exception propagation is not allowed
10060 -- and aborts are allowed:
10065 -- [Deep_]Finalize (Res.all);
10067 -- Abort_Undefer_Direct;
10070 elsif Abort_Allowed
then
10071 Abort_Only
: declare
10072 Blk_Stmts
: constant List_Id
:= New_List
;
10075 Append_To
(Blk_Stmts
, Build_Runtime_Call
(Loc
, RE_Abort_Defer
));
10076 Append_To
(Blk_Stmts
, Hook_Clear
);
10078 if Present
(Fin_Call
) then
10079 Append_To
(Blk_Stmts
, Fin_Call
);
10083 Build_Abort_Undefer_Block
(Loc
,
10084 Stmts
=> Blk_Stmts
,
10088 -- Otherwise generate:
10091 -- [Deep_]Finalize (Res.all);
10094 Append_To
(Stmts
, Hook_Clear
);
10096 if Present
(Fin_Call
) then
10097 Append_To
(Stmts
, Fin_Call
);
10100 end Process_Transient_Component_Completion
;
10102 ---------------------
10103 -- Sort_Case_Table --
10104 ---------------------
10106 procedure Sort_Case_Table
(Case_Table
: in out Case_Table_Type
) is
10107 L
: constant Int
:= Case_Table
'First;
10108 U
: constant Int
:= Case_Table
'Last;
10116 T
:= Case_Table
(K
+ 1);
10120 and then Expr_Value
(Case_Table
(J
- 1).Choice_Lo
) >
10121 Expr_Value
(T
.Choice_Lo
)
10123 Case_Table
(J
) := Case_Table
(J
- 1);
10127 Case_Table
(J
) := T
;
10130 end Sort_Case_Table
;
10132 ----------------------------
10133 -- Static_Array_Aggregate --
10134 ----------------------------
10136 function Static_Array_Aggregate
(N
: Node_Id
) return Boolean is
10137 function Is_Static_Component
(Nod
: Node_Id
) return Boolean;
10138 -- Return True if Nod has a compile-time known value and can be passed
10139 -- as is to the back-end without further expansion.
10141 ---------------------------
10142 -- Is_Static_Component --
10143 ---------------------------
10145 function Is_Static_Component
(Nod
: Node_Id
) return Boolean is
10147 if Nkind
(Nod
) in N_Integer_Literal | N_Real_Literal
then
10150 elsif Is_Entity_Name
(Nod
)
10151 and then Present
(Entity
(Nod
))
10152 and then Ekind
(Entity
(Nod
)) = E_Enumeration_Literal
10156 elsif Nkind
(Nod
) = N_Aggregate
10157 and then Compile_Time_Known_Aggregate
(Nod
)
10164 end Is_Static_Component
;
10168 Bounds
: constant Node_Id
:= Aggregate_Bounds
(N
);
10169 Typ
: constant Entity_Id
:= Etype
(N
);
10176 -- Start of processing for Static_Array_Aggregate
10179 if Is_Packed
(Typ
) or else Has_Discriminants
(Component_Type
(Typ
)) then
10183 if Present
(Bounds
)
10184 and then Nkind
(Bounds
) = N_Range
10185 and then Nkind
(Low_Bound
(Bounds
)) = N_Integer_Literal
10186 and then Nkind
(High_Bound
(Bounds
)) = N_Integer_Literal
10188 Lo
:= Low_Bound
(Bounds
);
10189 Hi
:= High_Bound
(Bounds
);
10191 if No
(Component_Associations
(N
)) then
10193 -- Verify that all components are static
10195 Expr
:= First
(Expressions
(N
));
10196 while Present
(Expr
) loop
10197 if not Is_Static_Component
(Expr
) then
10207 -- We allow only a single named association, either a static
10208 -- range or an others_clause, with a static expression.
10210 Expr
:= First
(Component_Associations
(N
));
10212 if Present
(Expressions
(N
)) then
10215 elsif Present
(Next
(Expr
)) then
10218 elsif Present
(Next
(First
(Choice_List
(Expr
)))) then
10222 -- The aggregate is static if all components are literals,
10223 -- or else all its components are static aggregates for the
10224 -- component type. We also limit the size of a static aggregate
10225 -- to prevent runaway static expressions.
10227 if not Is_Static_Component
(Expression
(Expr
)) then
10231 if not Aggr_Size_OK
(N
) then
10235 -- Create a positional aggregate with the right number of
10236 -- copies of the expression.
10238 Agg
:= Make_Aggregate
(Sloc
(N
), New_List
, No_List
);
10240 for I
in UI_To_Int
(Intval
(Lo
)) .. UI_To_Int
(Intval
(Hi
))
10242 Append_To
(Expressions
(Agg
), New_Copy
(Expression
(Expr
)));
10244 -- The copied expression must be analyzed and resolved.
10245 -- Besides setting the type, this ensures that static
10246 -- expressions are appropriately marked as such.
10248 Analyze_And_Resolve
10249 (Last
(Expressions
(Agg
)), Component_Type
(Typ
));
10252 Set_Aggregate_Bounds
(Agg
, Bounds
);
10253 Set_Etype
(Agg
, Typ
);
10254 Set_Analyzed
(Agg
);
10256 Set_Compile_Time_Known_Aggregate
(N
);
10265 end Static_Array_Aggregate
;
10267 ----------------------------------
10268 -- Two_Dim_Packed_Array_Handled --
10269 ----------------------------------
10271 function Two_Dim_Packed_Array_Handled
(N
: Node_Id
) return Boolean is
10272 Loc
: constant Source_Ptr
:= Sloc
(N
);
10273 Typ
: constant Entity_Id
:= Etype
(N
);
10274 Ctyp
: constant Entity_Id
:= Component_Type
(Typ
);
10275 Comp_Size
: constant Int
:= UI_To_Int
(Component_Size
(Typ
));
10276 Packed_Array
: constant Entity_Id
:=
10277 Packed_Array_Impl_Type
(Base_Type
(Typ
));
10279 One_Comp
: Node_Id
;
10280 -- Expression in original aggregate
10283 -- One-dimensional subaggregate
10287 -- For now, only deal with cases where an integral number of elements
10288 -- fit in a single byte. This includes the most common boolean case.
10290 if not (Comp_Size
= 1 or else
10291 Comp_Size
= 2 or else
10297 Convert_To_Positional
(N
, Handle_Bit_Packed
=> True);
10299 -- Verify that all components are static
10301 if Nkind
(N
) = N_Aggregate
10302 and then Compile_Time_Known_Aggregate
(N
)
10306 -- The aggregate may have been reanalyzed and converted already
10308 elsif Nkind
(N
) /= N_Aggregate
then
10311 -- If component associations remain, the aggregate is not static
10313 elsif Present
(Component_Associations
(N
)) then
10317 One_Dim
:= First
(Expressions
(N
));
10318 while Present
(One_Dim
) loop
10319 if Present
(Component_Associations
(One_Dim
)) then
10323 One_Comp
:= First
(Expressions
(One_Dim
));
10324 while Present
(One_Comp
) loop
10325 if not Is_OK_Static_Expression
(One_Comp
) then
10336 -- Two-dimensional aggregate is now fully positional so pack one
10337 -- dimension to create a static one-dimensional array, and rewrite
10338 -- as an unchecked conversion to the original type.
10341 Byte_Size
: constant Int
:= UI_To_Int
(Component_Size
(Packed_Array
));
10342 -- The packed array type is a byte array
10345 -- Number of components accumulated in current byte
10348 -- Assembled list of packed values for equivalent aggregate
10351 -- Integer value of component
10354 -- Step size for packing
10357 -- Endian-dependent start position for packing
10360 -- Current insertion position
10363 -- Component of packed array being assembled
10370 -- Account for endianness. See corresponding comment in
10371 -- Packed_Array_Aggregate_Handled concerning the following.
10373 if Bytes_Big_Endian
10375 xor Reverse_Storage_Order
(Base_Type
(Typ
))
10377 Init_Shift
:= Byte_Size
- Comp_Size
;
10378 Incr
:= -Comp_Size
;
10381 Incr
:= +Comp_Size
;
10384 -- Iterate over each subaggregate
10386 Shift
:= Init_Shift
;
10387 One_Dim
:= First
(Expressions
(N
));
10388 while Present
(One_Dim
) loop
10389 One_Comp
:= First
(Expressions
(One_Dim
));
10390 while Present
(One_Comp
) loop
10391 if Packed_Num
= Byte_Size
/ Comp_Size
then
10393 -- Byte is complete, add to list of expressions
10395 Append
(Make_Integer_Literal
(Sloc
(One_Dim
), Val
), Comps
);
10397 Shift
:= Init_Shift
;
10401 Comp_Val
:= Expr_Rep_Value
(One_Comp
);
10403 -- Adjust for bias, and strip proper number of bits
10405 if Has_Biased_Representation
(Ctyp
) then
10406 Comp_Val
:= Comp_Val
- Expr_Value
(Type_Low_Bound
(Ctyp
));
10409 Comp_Val
:= Comp_Val
mod Uint_2
** Comp_Size
;
10410 Val
:= UI_To_Int
(Val
+ Comp_Val
* Uint_2
** Shift
);
10411 Shift
:= Shift
+ Incr
;
10413 Packed_Num
:= Packed_Num
+ 1;
10420 if Packed_Num
> 0 then
10422 -- Add final incomplete byte if present
10424 Append
(Make_Integer_Literal
(Sloc
(One_Dim
), Val
), Comps
);
10428 Unchecked_Convert_To
(Typ
,
10429 Make_Qualified_Expression
(Loc
,
10430 Subtype_Mark
=> New_Occurrence_Of
(Packed_Array
, Loc
),
10431 Expression
=> Make_Aggregate
(Loc
, Expressions
=> Comps
))));
10432 Analyze_And_Resolve
(N
);
10435 end Two_Dim_Packed_Array_Handled
;