1 ------------------------------------------------------------------------------
3 -- GNAT COMPILER COMPONENTS --
9 -- Copyright (C) 1992-2012, 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 Atree
; use Atree
;
27 with Checks
; use Checks
;
28 with Debug
; use Debug
;
29 with Einfo
; use Einfo
;
30 with Elists
; use Elists
;
31 with Errout
; use Errout
;
32 with Expander
; use Expander
;
33 with Exp_Util
; use Exp_Util
;
34 with Exp_Ch3
; use Exp_Ch3
;
35 with Exp_Ch6
; use Exp_Ch6
;
36 with Exp_Ch7
; use Exp_Ch7
;
37 with Exp_Ch9
; use Exp_Ch9
;
38 with Exp_Disp
; use Exp_Disp
;
39 with Exp_Tss
; use Exp_Tss
;
40 with Fname
; use Fname
;
41 with Freeze
; use Freeze
;
42 with Itypes
; use Itypes
;
44 with Namet
; use Namet
;
45 with Nmake
; use Nmake
;
46 with Nlists
; use Nlists
;
48 with Restrict
; use Restrict
;
49 with Rident
; use Rident
;
50 with Rtsfind
; use Rtsfind
;
51 with Ttypes
; use Ttypes
;
53 with Sem_Aggr
; use Sem_Aggr
;
54 with Sem_Aux
; use Sem_Aux
;
55 with Sem_Ch3
; use Sem_Ch3
;
56 with Sem_Eval
; use Sem_Eval
;
57 with Sem_Res
; use Sem_Res
;
58 with Sem_Util
; use Sem_Util
;
59 with Sinfo
; use Sinfo
;
60 with Snames
; use Snames
;
61 with Stand
; use Stand
;
62 with Targparm
; use Targparm
;
63 with Tbuild
; use Tbuild
;
64 with Uintp
; use Uintp
;
66 package body Exp_Aggr
is
68 type Case_Bounds
is record
71 Choice_Node
: Node_Id
;
74 type Case_Table_Type
is array (Nat
range <>) of Case_Bounds
;
75 -- Table type used by Check_Case_Choices procedure
77 function Has_Default_Init_Comps
(N
: Node_Id
) return Boolean;
78 -- N is an aggregate (record or array). Checks the presence of default
79 -- initialization (<>) in any component (Ada 2005: AI-287).
81 function Is_Static_Dispatch_Table_Aggregate
(N
: Node_Id
) return Boolean;
82 -- Returns true if N is an aggregate used to initialize the components
83 -- of an statically allocated dispatch table.
86 (Obj_Type
: Entity_Id
;
87 Typ
: Entity_Id
) return Boolean;
88 -- A static array aggregate in an object declaration can in most cases be
89 -- expanded in place. The one exception is when the aggregate is given
90 -- with component associations that specify different bounds from those of
91 -- the type definition in the object declaration. In this pathological
92 -- case the aggregate must slide, and we must introduce an intermediate
93 -- temporary to hold it.
95 -- The same holds in an assignment to one-dimensional array of arrays,
96 -- when a component may be given with bounds that differ from those of the
99 procedure Sort_Case_Table
(Case_Table
: in out Case_Table_Type
);
100 -- Sort the Case Table using the Lower Bound of each Choice as the key.
101 -- A simple insertion sort is used since the number of choices in a case
102 -- statement of variant part will usually be small and probably in near
105 ------------------------------------------------------
106 -- Local subprograms for Record Aggregate Expansion --
107 ------------------------------------------------------
109 function Build_Record_Aggr_Code
112 Lhs
: Node_Id
) return List_Id
;
113 -- N is an N_Aggregate or an N_Extension_Aggregate. Typ is the type of the
114 -- aggregate. Target is an expression containing the location on which the
115 -- component by component assignments will take place. Returns the list of
116 -- assignments plus all other adjustments needed for tagged and controlled
119 procedure Convert_To_Assignments
(N
: Node_Id
; Typ
: Entity_Id
);
120 -- N is an N_Aggregate or an N_Extension_Aggregate. Typ is the type of the
121 -- aggregate (which can only be a record type, this procedure is only used
122 -- for record types). Transform the given aggregate into a sequence of
123 -- assignments performed component by component.
125 procedure Expand_Record_Aggregate
127 Orig_Tag
: Node_Id
:= Empty
;
128 Parent_Expr
: Node_Id
:= Empty
);
129 -- This is the top level procedure for record aggregate expansion.
130 -- Expansion for record aggregates needs expand aggregates for tagged
131 -- record types. Specifically Expand_Record_Aggregate adds the Tag
132 -- field in front of the Component_Association list that was created
133 -- during resolution by Resolve_Record_Aggregate.
135 -- N is the record aggregate node.
136 -- Orig_Tag is the value of the Tag that has to be provided for this
137 -- specific aggregate. It carries the tag corresponding to the type
138 -- of the outermost aggregate during the recursive expansion
139 -- Parent_Expr is the ancestor part of the original extension
142 function Has_Mutable_Components
(Typ
: Entity_Id
) return Boolean;
143 -- Return true if one of the component is of a discriminated type with
144 -- defaults. An aggregate for a type with mutable components must be
145 -- expanded into individual assignments.
147 procedure Initialize_Discriminants
(N
: Node_Id
; Typ
: Entity_Id
);
148 -- If the type of the aggregate is a type extension with renamed discrimi-
149 -- nants, we must initialize the hidden discriminants of the parent.
150 -- Otherwise, the target object must not be initialized. The discriminants
151 -- are initialized by calling the initialization procedure for the type.
152 -- This is incorrect if the initialization of other components has any
153 -- side effects. We restrict this call to the case where the parent type
154 -- has a variant part, because this is the only case where the hidden
155 -- discriminants are accessed, namely when calling discriminant checking
156 -- functions of the parent type, and when applying a stream attribute to
157 -- an object of the derived type.
159 -----------------------------------------------------
160 -- Local Subprograms for Array Aggregate Expansion --
161 -----------------------------------------------------
163 function Aggr_Size_OK
(N
: Node_Id
; Typ
: Entity_Id
) return Boolean;
164 -- Very large static aggregates present problems to the back-end, and are
165 -- transformed into assignments and loops. This function verifies that the
166 -- total number of components of an aggregate is acceptable for rewriting
167 -- into a purely positional static form. Aggr_Size_OK must be called before
170 -- This function also detects and warns about one-component aggregates that
171 -- appear in a non-static context. Even if the component value is static,
172 -- such an aggregate must be expanded into an assignment.
174 function Backend_Processing_Possible
(N
: Node_Id
) return Boolean;
175 -- This function checks if array aggregate N can be processed directly
176 -- by the backend. If this is the case True is returned.
178 function Build_Array_Aggr_Code
183 Scalar_Comp
: Boolean;
184 Indexes
: List_Id
:= No_List
) return List_Id
;
185 -- This recursive routine returns a list of statements containing the
186 -- loops and assignments that are needed for the expansion of the array
189 -- N is the (sub-)aggregate node to be expanded into code. This node has
190 -- been fully analyzed, and its Etype is properly set.
192 -- Index is the index node corresponding to the array sub-aggregate N
194 -- Into is the target expression into which we are copying the aggregate.
195 -- Note that this node may not have been analyzed yet, and so the Etype
196 -- field may not be set.
198 -- Scalar_Comp is True if the component type of the aggregate is scalar
200 -- Indexes is the current list of expressions used to index the object we
203 procedure Convert_Array_Aggr_In_Allocator
207 -- If the aggregate appears within an allocator and can be expanded in
208 -- place, this routine generates the individual assignments to components
209 -- of the designated object. This is an optimization over the general
210 -- case, where a temporary is first created on the stack and then used to
211 -- construct the allocated object on the heap.
213 procedure Convert_To_Positional
215 Max_Others_Replicate
: Nat
:= 5;
216 Handle_Bit_Packed
: Boolean := False);
217 -- If possible, convert named notation to positional notation. This
218 -- conversion is possible only in some static cases. If the conversion is
219 -- possible, then N is rewritten with the analyzed converted aggregate.
220 -- The parameter Max_Others_Replicate controls the maximum number of
221 -- values corresponding to an others choice that will be converted to
222 -- positional notation (the default of 5 is the normal limit, and reflects
223 -- the fact that normally the loop is better than a lot of separate
224 -- assignments). Note that this limit gets overridden in any case if
225 -- either of the restrictions No_Elaboration_Code or No_Implicit_Loops is
226 -- set. The parameter Handle_Bit_Packed is usually set False (since we do
227 -- not expect the back end to handle bit packed arrays, so the normal case
228 -- of conversion is pointless), but in the special case of a call from
229 -- Packed_Array_Aggregate_Handled, we set this parameter to True, since
230 -- these are cases we handle in there.
232 -- It would seem worthwhile to have a higher default value for Max_Others_
233 -- replicate, but aggregates in the compiler make this impossible: the
234 -- compiler bootstrap fails if Max_Others_Replicate is greater than 25.
235 -- This is unexpected ???
237 procedure Expand_Array_Aggregate
(N
: Node_Id
);
238 -- This is the top-level routine to perform array aggregate expansion.
239 -- N is the N_Aggregate node to be expanded.
241 function Is_Two_Dim_Packed_Array
(Typ
: Entity_Id
) return Boolean;
242 -- For two-dimensional packed aggregates with constant bounds and constant
243 -- components, it is preferable to pack the inner aggregates because the
244 -- whole matrix can then be presented to the back-end as a one-dimensional
245 -- list of literals. This is much more efficient than expanding into single
246 -- component assignments. This function determines if the type Typ is for
247 -- an array that is suitable for this optimization: it returns True if Typ
248 -- is a two dimensional bit packed array with component size 1, 2, or 4.
250 function Late_Expansion
253 Target
: Node_Id
) return List_Id
;
254 -- This routine implements top-down expansion of nested aggregates. In
255 -- doing so, it avoids the generation of temporaries at each level. N is
256 -- a nested record or array aggregate with the Expansion_Delayed flag.
257 -- Typ is the expected type of the aggregate. Target is a (duplicatable)
258 -- expression that will hold the result of the aggregate expansion.
260 function Make_OK_Assignment_Statement
263 Expression
: Node_Id
) return Node_Id
;
264 -- This is like Make_Assignment_Statement, except that Assignment_OK
265 -- is set in the left operand. All assignments built by this unit use
266 -- this routine. This is needed to deal with assignments to initialized
267 -- constants that are done in place.
269 function Number_Of_Choices
(N
: Node_Id
) return Nat
;
270 -- Returns the number of discrete choices (not including the others choice
271 -- if present) contained in (sub-)aggregate N.
273 function Packed_Array_Aggregate_Handled
(N
: Node_Id
) return Boolean;
274 -- Given an array aggregate, this function handles the case of a packed
275 -- array aggregate with all constant values, where the aggregate can be
276 -- evaluated at compile time. If this is possible, then N is rewritten
277 -- to be its proper compile time value with all the components properly
278 -- assembled. The expression is analyzed and resolved and True is returned.
279 -- If this transformation is not possible, N is unchanged and False is
282 function Safe_Slice_Assignment
(N
: Node_Id
) return Boolean;
283 -- If a slice assignment has an aggregate with a single others_choice,
284 -- the assignment can be done in place even if bounds are not static,
285 -- by converting it into a loop over the discrete range of the slice.
287 function Two_Dim_Packed_Array_Handled
(N
: Node_Id
) return Boolean;
288 -- If the type of the aggregate is a two-dimensional bit_packed array
289 -- it may be transformed into an array of bytes with constant values,
290 -- and presented to the back-end as a static value. The function returns
291 -- false if this transformation cannot be performed. THis is similar to,
292 -- and reuses part of the machinery in Packed_Array_Aggregate_Handled.
298 function Aggr_Size_OK
(N
: Node_Id
; Typ
: Entity_Id
) return Boolean is
306 -- The following constant determines the maximum size of an array
307 -- aggregate produced by converting named to positional notation (e.g.
308 -- from others clauses). This avoids running away with attempts to
309 -- convert huge aggregates, which hit memory limits in the backend.
311 -- The normal limit is 5000, but we increase this limit to 2**24 (about
312 -- 16 million) if Restrictions (No_Elaboration_Code) or Restrictions
313 -- (No_Implicit_Loops) is specified, since in either case we are at
314 -- risk of declaring the program illegal because of this limit. We also
315 -- increase the limit when Static_Elaboration_Desired, given that this
316 -- means that objects are intended to be placed in data memory.
318 -- We also increase the limit if the aggregate is for a packed two-
319 -- dimensional array, because if components are static it is much more
320 -- efficient to construct a one-dimensional equivalent array with static
323 Max_Aggr_Size
: constant Nat
:=
324 5000 + (2 ** 24 - 5000) *
326 (Restriction_Active
(No_Elaboration_Code
)
327 or else Restriction_Active
(No_Implicit_Loops
)
328 or else Is_Two_Dim_Packed_Array
(Typ
)
329 or else ((Ekind
(Current_Scope
) = E_Package
330 and then Static_Elaboration_Desired
(Current_Scope
))));
332 function Component_Count
(T
: Entity_Id
) return Int
;
333 -- The limit is applied to the total number of components that the
334 -- aggregate will have, which is the number of static expressions
335 -- that will appear in the flattened array. This requires a recursive
336 -- computation of the number of scalar components of the structure.
338 ---------------------
339 -- Component_Count --
340 ---------------------
342 function Component_Count
(T
: Entity_Id
) return Int
is
347 if Is_Scalar_Type
(T
) then
350 elsif Is_Record_Type
(T
) then
351 Comp
:= First_Component
(T
);
352 while Present
(Comp
) loop
353 Res
:= Res
+ Component_Count
(Etype
(Comp
));
354 Next_Component
(Comp
);
359 elsif Is_Array_Type
(T
) then
361 Lo
: constant Node_Id
:=
362 Type_Low_Bound
(Etype
(First_Index
(T
)));
363 Hi
: constant Node_Id
:=
364 Type_High_Bound
(Etype
(First_Index
(T
)));
366 Siz
: constant Int
:= Component_Count
(Component_Type
(T
));
369 if not Compile_Time_Known_Value
(Lo
)
370 or else not Compile_Time_Known_Value
(Hi
)
375 Siz
* UI_To_Int
(Expr_Value
(Hi
) - Expr_Value
(Lo
) + 1);
380 -- Can only be a null for an access type
386 -- Start of processing for Aggr_Size_OK
389 Siz
:= Component_Count
(Component_Type
(Typ
));
391 Indx
:= First_Index
(Typ
);
392 while Present
(Indx
) loop
393 Lo
:= Type_Low_Bound
(Etype
(Indx
));
394 Hi
:= Type_High_Bound
(Etype
(Indx
));
396 -- Bounds need to be known at compile time
398 if not Compile_Time_Known_Value
(Lo
)
399 or else not Compile_Time_Known_Value
(Hi
)
404 Lov
:= Expr_Value
(Lo
);
405 Hiv
:= Expr_Value
(Hi
);
407 -- A flat array is always safe
413 -- One-component aggregates are suspicious, and if the context type
414 -- is an object declaration with non-static bounds it will trip gcc;
415 -- such an aggregate must be expanded into a single assignment.
418 and then Nkind
(Parent
(N
)) = N_Object_Declaration
421 Index_Type
: constant Entity_Id
:=
423 (First_Index
(Etype
(Defining_Identifier
(Parent
(N
)))));
427 if not Compile_Time_Known_Value
(Type_Low_Bound
(Index_Type
))
428 or else not Compile_Time_Known_Value
429 (Type_High_Bound
(Index_Type
))
431 if Present
(Component_Associations
(N
)) then
433 First
(Choices
(First
(Component_Associations
(N
))));
434 if Is_Entity_Name
(Indx
)
435 and then not Is_Type
(Entity
(Indx
))
438 ("single component aggregate in non-static context?",
440 Error_Msg_N
("\maybe subtype name was meant?", Indx
);
450 Rng
: constant Uint
:= Hiv
- Lov
+ 1;
453 -- Check if size is too large
455 if not UI_Is_In_Int_Range
(Rng
) then
459 Siz
:= Siz
* UI_To_Int
(Rng
);
463 or else Siz
> Max_Aggr_Size
468 -- Bounds must be in integer range, for later array construction
470 if not UI_Is_In_Int_Range
(Lov
)
472 not UI_Is_In_Int_Range
(Hiv
)
483 ---------------------------------
484 -- Backend_Processing_Possible --
485 ---------------------------------
487 -- Backend processing by Gigi/gcc is possible only if all the following
488 -- conditions are met:
490 -- 1. N is fully positional
492 -- 2. N is not a bit-packed array aggregate;
494 -- 3. The size of N's array type must be known at compile time. Note
495 -- that this implies that the component size is also known
497 -- 4. The array type of N does not follow the Fortran layout convention
498 -- or if it does it must be 1 dimensional.
500 -- 5. The array component type may not be tagged (which could necessitate
501 -- reassignment of proper tags).
503 -- 6. The array component type must not have unaligned bit components
505 -- 7. None of the components of the aggregate may be bit unaligned
508 -- 8. There cannot be delayed components, since we do not know enough
509 -- at this stage to know if back end processing is possible.
511 -- 9. There cannot be any discriminated record components, since the
512 -- back end cannot handle this complex case.
514 -- 10. No controlled actions need to be generated for components
516 -- 11. For a VM back end, the array should have no aliased components
518 function Backend_Processing_Possible
(N
: Node_Id
) return Boolean is
519 Typ
: constant Entity_Id
:= Etype
(N
);
520 -- Typ is the correct constrained array subtype of the aggregate
522 function Component_Check
(N
: Node_Id
; Index
: Node_Id
) return Boolean;
523 -- This routine checks components of aggregate N, enforcing checks
524 -- 1, 7, 8, and 9. In the multi-dimensional case, these checks are
525 -- performed on subaggregates. The Index value is the current index
526 -- being checked in the multi-dimensional case.
528 ---------------------
529 -- Component_Check --
530 ---------------------
532 function Component_Check
(N
: Node_Id
; Index
: Node_Id
) return Boolean is
536 -- Checks 1: (no component associations)
538 if Present
(Component_Associations
(N
)) then
542 -- Checks on components
544 -- Recurse to check subaggregates, which may appear in qualified
545 -- expressions. If delayed, the front-end will have to expand.
546 -- If the component is a discriminated record, treat as non-static,
547 -- as the back-end cannot handle this properly.
549 Expr
:= First
(Expressions
(N
));
550 while Present
(Expr
) loop
552 -- Checks 8: (no delayed components)
554 if Is_Delayed_Aggregate
(Expr
) then
558 -- Checks 9: (no discriminated records)
560 if Present
(Etype
(Expr
))
561 and then Is_Record_Type
(Etype
(Expr
))
562 and then Has_Discriminants
(Etype
(Expr
))
567 -- Checks 7. Component must not be bit aligned component
569 if Possible_Bit_Aligned_Component
(Expr
) then
573 -- Recursion to following indexes for multiple dimension case
575 if Present
(Next_Index
(Index
))
576 and then not Component_Check
(Expr
, Next_Index
(Index
))
581 -- All checks for that component finished, on to next
589 -- Start of processing for Backend_Processing_Possible
592 -- Checks 2 (array not bit packed) and 10 (no controlled actions)
594 if Is_Bit_Packed_Array
(Typ
) or else Needs_Finalization
(Typ
) then
598 -- If component is limited, aggregate must be expanded because each
599 -- component assignment must be built in place.
601 if Is_Immutably_Limited_Type
(Component_Type
(Typ
)) then
605 -- Checks 4 (array must not be multi-dimensional Fortran case)
607 if Convention
(Typ
) = Convention_Fortran
608 and then Number_Dimensions
(Typ
) > 1
613 -- Checks 3 (size of array must be known at compile time)
615 if not Size_Known_At_Compile_Time
(Typ
) then
619 -- Checks on components
621 if not Component_Check
(N
, First_Index
(Typ
)) then
625 -- Checks 5 (if the component type is tagged, then we may need to do
626 -- tag adjustments. Perhaps this should be refined to check for any
627 -- component associations that actually need tag adjustment, similar
628 -- to the test in Component_Not_OK_For_Backend for record aggregates
629 -- with tagged components, but not clear whether it's worthwhile ???;
630 -- in the case of the JVM, object tags are handled implicitly)
632 if Is_Tagged_Type
(Component_Type
(Typ
))
633 and then Tagged_Type_Expansion
638 -- Checks 6 (component type must not have bit aligned components)
640 if Type_May_Have_Bit_Aligned_Components
(Component_Type
(Typ
)) then
644 -- Checks 11: Array aggregates with aliased components are currently
645 -- not well supported by the VM backend; disable temporarily this
646 -- backend processing until it is definitely supported.
648 if VM_Target
/= No_VM
649 and then Has_Aliased_Components
(Base_Type
(Typ
))
654 -- Backend processing is possible
656 Set_Size_Known_At_Compile_Time
(Etype
(N
), True);
658 end Backend_Processing_Possible
;
660 ---------------------------
661 -- Build_Array_Aggr_Code --
662 ---------------------------
664 -- The code that we generate from a one dimensional aggregate is
666 -- 1. If the sub-aggregate contains discrete choices we
668 -- (a) Sort the discrete choices
670 -- (b) Otherwise for each discrete choice that specifies a range we
671 -- emit a loop. If a range specifies a maximum of three values, or
672 -- we are dealing with an expression we emit a sequence of
673 -- assignments instead of a loop.
675 -- (c) Generate the remaining loops to cover the others choice if any
677 -- 2. If the aggregate contains positional elements we
679 -- (a) translate the positional elements in a series of assignments
681 -- (b) Generate a final loop to cover the others choice if any.
682 -- Note that this final loop has to be a while loop since the case
684 -- L : Integer := Integer'Last;
685 -- H : Integer := Integer'Last;
686 -- A : array (L .. H) := (1, others =>0);
688 -- cannot be handled by a for loop. Thus for the following
690 -- array (L .. H) := (.. positional elements.., others =>E);
692 -- we always generate something like:
694 -- J : Index_Type := Index_Of_Last_Positional_Element;
696 -- J := Index_Base'Succ (J)
700 function Build_Array_Aggr_Code
705 Scalar_Comp
: Boolean;
706 Indexes
: List_Id
:= No_List
) return List_Id
708 Loc
: constant Source_Ptr
:= Sloc
(N
);
709 Index_Base
: constant Entity_Id
:= Base_Type
(Etype
(Index
));
710 Index_Base_L
: constant Node_Id
:= Type_Low_Bound
(Index_Base
);
711 Index_Base_H
: constant Node_Id
:= Type_High_Bound
(Index_Base
);
713 function Add
(Val
: Int
; To
: Node_Id
) return Node_Id
;
714 -- Returns an expression where Val is added to expression To, unless
715 -- To+Val is provably out of To's base type range. To must be an
716 -- already analyzed expression.
718 function Empty_Range
(L
, H
: Node_Id
) return Boolean;
719 -- Returns True if the range defined by L .. H is certainly empty
721 function Equal
(L
, H
: Node_Id
) return Boolean;
722 -- Returns True if L = H for sure
724 function Index_Base_Name
return Node_Id
;
725 -- Returns a new reference to the index type name
727 function Gen_Assign
(Ind
: Node_Id
; Expr
: Node_Id
) return List_Id
;
728 -- Ind must be a side-effect free expression. If the input aggregate
729 -- N to Build_Loop contains no sub-aggregates, then this function
730 -- returns the assignment statement:
732 -- Into (Indexes, Ind) := Expr;
734 -- Otherwise we call Build_Code recursively
736 -- Ada 2005 (AI-287): In case of default initialized component, Expr
737 -- is empty and we generate a call to the corresponding IP subprogram.
739 function Gen_Loop
(L
, H
: Node_Id
; Expr
: Node_Id
) return List_Id
;
740 -- Nodes L and H must be side-effect free expressions.
741 -- If the input aggregate N to Build_Loop contains no sub-aggregates,
742 -- This routine returns the for loop statement
744 -- for J in Index_Base'(L) .. Index_Base'(H) loop
745 -- Into (Indexes, J) := Expr;
748 -- Otherwise we call Build_Code recursively.
749 -- As an optimization if the loop covers 3 or less scalar elements we
750 -- generate a sequence of assignments.
752 function Gen_While
(L
, H
: Node_Id
; Expr
: Node_Id
) return List_Id
;
753 -- Nodes L and H must be side-effect free expressions.
754 -- If the input aggregate N to Build_Loop contains no sub-aggregates,
755 -- This routine returns the while loop statement
757 -- J : Index_Base := L;
759 -- J := Index_Base'Succ (J);
760 -- Into (Indexes, J) := Expr;
763 -- Otherwise we call Build_Code recursively
765 function Local_Compile_Time_Known_Value
(E
: Node_Id
) return Boolean;
766 function Local_Expr_Value
(E
: Node_Id
) return Uint
;
767 -- These two Local routines are used to replace the corresponding ones
768 -- in sem_eval because while processing the bounds of an aggregate with
769 -- discrete choices whose index type is an enumeration, we build static
770 -- expressions not recognized by Compile_Time_Known_Value as such since
771 -- they have not yet been analyzed and resolved. All the expressions in
772 -- question are things like Index_Base_Name'Val (Const) which we can
773 -- easily recognize as being constant.
779 function Add
(Val
: Int
; To
: Node_Id
) return Node_Id
is
784 U_Val
: constant Uint
:= UI_From_Int
(Val
);
787 -- Note: do not try to optimize the case of Val = 0, because
788 -- we need to build a new node with the proper Sloc value anyway.
790 -- First test if we can do constant folding
792 if Local_Compile_Time_Known_Value
(To
) then
793 U_To
:= Local_Expr_Value
(To
) + Val
;
795 -- Determine if our constant is outside the range of the index.
796 -- If so return an Empty node. This empty node will be caught
797 -- by Empty_Range below.
799 if Compile_Time_Known_Value
(Index_Base_L
)
800 and then U_To
< Expr_Value
(Index_Base_L
)
804 elsif Compile_Time_Known_Value
(Index_Base_H
)
805 and then U_To
> Expr_Value
(Index_Base_H
)
810 Expr_Pos
:= Make_Integer_Literal
(Loc
, U_To
);
811 Set_Is_Static_Expression
(Expr_Pos
);
813 if not Is_Enumeration_Type
(Index_Base
) then
816 -- If we are dealing with enumeration return
817 -- Index_Base'Val (Expr_Pos)
821 Make_Attribute_Reference
823 Prefix
=> Index_Base_Name
,
824 Attribute_Name
=> Name_Val
,
825 Expressions
=> New_List
(Expr_Pos
));
831 -- If we are here no constant folding possible
833 if not Is_Enumeration_Type
(Index_Base
) then
836 Left_Opnd
=> Duplicate_Subexpr
(To
),
837 Right_Opnd
=> Make_Integer_Literal
(Loc
, U_Val
));
839 -- If we are dealing with enumeration return
840 -- Index_Base'Val (Index_Base'Pos (To) + Val)
844 Make_Attribute_Reference
846 Prefix
=> Index_Base_Name
,
847 Attribute_Name
=> Name_Pos
,
848 Expressions
=> New_List
(Duplicate_Subexpr
(To
)));
853 Right_Opnd
=> Make_Integer_Literal
(Loc
, U_Val
));
856 Make_Attribute_Reference
858 Prefix
=> Index_Base_Name
,
859 Attribute_Name
=> Name_Val
,
860 Expressions
=> New_List
(Expr_Pos
));
870 function Empty_Range
(L
, H
: Node_Id
) return Boolean is
871 Is_Empty
: Boolean := False;
876 -- First check if L or H were already detected as overflowing the
877 -- index base range type by function Add above. If this is so Add
878 -- returns the empty node.
880 if No
(L
) or else No
(H
) then
887 -- L > H range is empty
893 -- B_L > H range must be empty
899 -- L > B_H range must be empty
903 High
:= Index_Base_H
;
906 if Local_Compile_Time_Known_Value
(Low
)
907 and then Local_Compile_Time_Known_Value
(High
)
910 UI_Gt
(Local_Expr_Value
(Low
), Local_Expr_Value
(High
));
923 function Equal
(L
, H
: Node_Id
) return Boolean is
928 elsif Local_Compile_Time_Known_Value
(L
)
929 and then Local_Compile_Time_Known_Value
(H
)
931 return UI_Eq
(Local_Expr_Value
(L
), Local_Expr_Value
(H
));
941 function Gen_Assign
(Ind
: Node_Id
; Expr
: Node_Id
) return List_Id
is
942 L
: constant List_Id
:= New_List
;
945 New_Indexes
: List_Id
;
946 Indexed_Comp
: Node_Id
;
948 Comp_Type
: Entity_Id
:= Empty
;
950 function Add_Loop_Actions
(Lis
: List_Id
) return List_Id
;
951 -- Collect insert_actions generated in the construction of a
952 -- loop, and prepend them to the sequence of assignments to
953 -- complete the eventual body of the loop.
955 ----------------------
956 -- Add_Loop_Actions --
957 ----------------------
959 function Add_Loop_Actions
(Lis
: List_Id
) return List_Id
is
963 -- Ada 2005 (AI-287): Do nothing else in case of default
964 -- initialized component.
969 elsif Nkind
(Parent
(Expr
)) = N_Component_Association
970 and then Present
(Loop_Actions
(Parent
(Expr
)))
972 Append_List
(Lis
, Loop_Actions
(Parent
(Expr
)));
973 Res
:= Loop_Actions
(Parent
(Expr
));
974 Set_Loop_Actions
(Parent
(Expr
), No_List
);
980 end Add_Loop_Actions
;
982 -- Start of processing for Gen_Assign
986 New_Indexes
:= New_List
;
988 New_Indexes
:= New_Copy_List_Tree
(Indexes
);
991 Append_To
(New_Indexes
, Ind
);
993 if Present
(Next_Index
(Index
)) then
996 Build_Array_Aggr_Code
999 Index
=> Next_Index
(Index
),
1001 Scalar_Comp
=> Scalar_Comp
,
1002 Indexes
=> New_Indexes
));
1005 -- If we get here then we are at a bottom-level (sub-)aggregate
1009 (Make_Indexed_Component
(Loc
,
1010 Prefix
=> New_Copy_Tree
(Into
),
1011 Expressions
=> New_Indexes
));
1013 Set_Assignment_OK
(Indexed_Comp
);
1015 -- Ada 2005 (AI-287): In case of default initialized component, Expr
1016 -- is not present (and therefore we also initialize Expr_Q to empty).
1020 elsif Nkind
(Expr
) = N_Qualified_Expression
then
1021 Expr_Q
:= Expression
(Expr
);
1026 if Present
(Etype
(N
))
1027 and then Etype
(N
) /= Any_Composite
1029 Comp_Type
:= Component_Type
(Etype
(N
));
1030 pragma Assert
(Comp_Type
= Ctype
); -- AI-287
1032 elsif Present
(Next
(First
(New_Indexes
))) then
1034 -- Ada 2005 (AI-287): Do nothing in case of default initialized
1035 -- component because we have received the component type in
1036 -- the formal parameter Ctype.
1038 -- ??? Some assert pragmas have been added to check if this new
1039 -- formal can be used to replace this code in all cases.
1041 if Present
(Expr
) then
1043 -- This is a multidimensional array. Recover the component
1044 -- type from the outermost aggregate, because subaggregates
1045 -- do not have an assigned type.
1052 while Present
(P
) loop
1053 if Nkind
(P
) = N_Aggregate
1054 and then Present
(Etype
(P
))
1056 Comp_Type
:= Component_Type
(Etype
(P
));
1064 pragma Assert
(Comp_Type
= Ctype
); -- AI-287
1069 -- Ada 2005 (AI-287): We only analyze the expression in case of non-
1070 -- default initialized components (otherwise Expr_Q is not present).
1073 and then Nkind_In
(Expr_Q
, N_Aggregate
, N_Extension_Aggregate
)
1075 -- At this stage the Expression may not have been analyzed yet
1076 -- because the array aggregate code has not been updated to use
1077 -- the Expansion_Delayed flag and avoid analysis altogether to
1078 -- solve the same problem (see Resolve_Aggr_Expr). So let us do
1079 -- the analysis of non-array aggregates now in order to get the
1080 -- value of Expansion_Delayed flag for the inner aggregate ???
1082 if Present
(Comp_Type
) and then not Is_Array_Type
(Comp_Type
) then
1083 Analyze_And_Resolve
(Expr_Q
, Comp_Type
);
1086 if Is_Delayed_Aggregate
(Expr_Q
) then
1088 -- This is either a subaggregate of a multidimensional array,
1089 -- or a component of an array type whose component type is
1090 -- also an array. In the latter case, the expression may have
1091 -- component associations that provide different bounds from
1092 -- those of the component type, and sliding must occur. Instead
1093 -- of decomposing the current aggregate assignment, force the
1094 -- re-analysis of the assignment, so that a temporary will be
1095 -- generated in the usual fashion, and sliding will take place.
1097 if Nkind
(Parent
(N
)) = N_Assignment_Statement
1098 and then Is_Array_Type
(Comp_Type
)
1099 and then Present
(Component_Associations
(Expr_Q
))
1100 and then Must_Slide
(Comp_Type
, Etype
(Expr_Q
))
1102 Set_Expansion_Delayed
(Expr_Q
, False);
1103 Set_Analyzed
(Expr_Q
, False);
1108 Late_Expansion
(Expr_Q
, Etype
(Expr_Q
), Indexed_Comp
));
1113 -- Ada 2005 (AI-287): In case of default initialized component, call
1114 -- the initialization subprogram associated with the component type.
1115 -- If the component type is an access type, add an explicit null
1116 -- assignment, because for the back-end there is an initialization
1117 -- present for the whole aggregate, and no default initialization
1120 -- In addition, if the component type is controlled, we must call
1121 -- its Initialize procedure explicitly, because there is no explicit
1122 -- object creation that will invoke it otherwise.
1125 if Present
(Base_Init_Proc
(Base_Type
(Ctype
)))
1126 or else Has_Task
(Base_Type
(Ctype
))
1129 Build_Initialization_Call
(Loc
,
1130 Id_Ref
=> Indexed_Comp
,
1132 With_Default_Init
=> True));
1134 elsif Is_Access_Type
(Ctype
) then
1136 Make_Assignment_Statement
(Loc
,
1137 Name
=> Indexed_Comp
,
1138 Expression
=> Make_Null
(Loc
)));
1141 if Needs_Finalization
(Ctype
) then
1144 Obj_Ref
=> New_Copy_Tree
(Indexed_Comp
),
1149 -- Now generate the assignment with no associated controlled
1150 -- actions since the target of the assignment may not have been
1151 -- initialized, it is not possible to Finalize it as expected by
1152 -- normal controlled assignment. The rest of the controlled
1153 -- actions are done manually with the proper finalization list
1154 -- coming from the context.
1157 Make_OK_Assignment_Statement
(Loc
,
1158 Name
=> Indexed_Comp
,
1159 Expression
=> New_Copy_Tree
(Expr
));
1161 if Present
(Comp_Type
) and then Needs_Finalization
(Comp_Type
) then
1162 Set_No_Ctrl_Actions
(A
);
1164 -- If this is an aggregate for an array of arrays, each
1165 -- sub-aggregate will be expanded as well, and even with
1166 -- No_Ctrl_Actions the assignments of inner components will
1167 -- require attachment in their assignments to temporaries.
1168 -- These temporaries must be finalized for each subaggregate,
1169 -- to prevent multiple attachments of the same temporary
1170 -- location to same finalization chain (and consequently
1171 -- circular lists). To ensure that finalization takes place
1172 -- for each subaggregate we wrap the assignment in a block.
1174 if Is_Array_Type
(Comp_Type
)
1175 and then Nkind
(Expr
) = N_Aggregate
1178 Make_Block_Statement
(Loc
,
1179 Handled_Statement_Sequence
=>
1180 Make_Handled_Sequence_Of_Statements
(Loc
,
1181 Statements
=> New_List
(A
)));
1187 -- Adjust the tag if tagged (because of possible view
1188 -- conversions), unless compiling for a VM where
1189 -- tags are implicit.
1191 if Present
(Comp_Type
)
1192 and then Is_Tagged_Type
(Comp_Type
)
1193 and then Tagged_Type_Expansion
1196 Full_Typ
: constant Entity_Id
:= Underlying_Type
(Comp_Type
);
1200 Make_OK_Assignment_Statement
(Loc
,
1202 Make_Selected_Component
(Loc
,
1203 Prefix
=> New_Copy_Tree
(Indexed_Comp
),
1206 (First_Tag_Component
(Full_Typ
), Loc
)),
1209 Unchecked_Convert_To
(RTE
(RE_Tag
),
1211 (Node
(First_Elmt
(Access_Disp_Table
(Full_Typ
))),
1218 -- Adjust and attach the component to the proper final list, which
1219 -- can be the controller of the outer record object or the final
1220 -- list associated with the scope.
1222 -- If the component is itself an array of controlled types, whose
1223 -- value is given by a sub-aggregate, then the attach calls have
1224 -- been generated when individual subcomponent are assigned, and
1225 -- must not be done again to prevent malformed finalization chains
1226 -- (see comments above, concerning the creation of a block to hold
1227 -- inner finalization actions).
1229 if Present
(Comp_Type
)
1230 and then Needs_Finalization
(Comp_Type
)
1231 and then not Is_Limited_Type
(Comp_Type
)
1233 (Is_Array_Type
(Comp_Type
)
1234 and then Is_Controlled
(Component_Type
(Comp_Type
))
1235 and then Nkind
(Expr
) = N_Aggregate
)
1239 Obj_Ref
=> New_Copy_Tree
(Indexed_Comp
),
1244 return Add_Loop_Actions
(L
);
1251 function Gen_Loop
(L
, H
: Node_Id
; Expr
: Node_Id
) return List_Id
is
1261 -- Index_Base'(L) .. Index_Base'(H)
1263 L_Iteration_Scheme
: Node_Id
;
1264 -- L_J in Index_Base'(L) .. Index_Base'(H)
1267 -- The statements to execute in the loop
1269 S
: constant List_Id
:= New_List
;
1270 -- List of statements
1273 -- Copy of expression tree, used for checking purposes
1276 -- If loop bounds define an empty range return the null statement
1278 if Empty_Range
(L
, H
) then
1279 Append_To
(S
, Make_Null_Statement
(Loc
));
1281 -- Ada 2005 (AI-287): Nothing else need to be done in case of
1282 -- default initialized component.
1288 -- The expression must be type-checked even though no component
1289 -- of the aggregate will have this value. This is done only for
1290 -- actual components of the array, not for subaggregates. Do
1291 -- the check on a copy, because the expression may be shared
1292 -- among several choices, some of which might be non-null.
1294 if Present
(Etype
(N
))
1295 and then Is_Array_Type
(Etype
(N
))
1296 and then No
(Next_Index
(Index
))
1298 Expander_Mode_Save_And_Set
(False);
1299 Tcopy
:= New_Copy_Tree
(Expr
);
1300 Set_Parent
(Tcopy
, N
);
1301 Analyze_And_Resolve
(Tcopy
, Component_Type
(Etype
(N
)));
1302 Expander_Mode_Restore
;
1308 -- If loop bounds are the same then generate an assignment
1310 elsif Equal
(L
, H
) then
1311 return Gen_Assign
(New_Copy_Tree
(L
), Expr
);
1313 -- If H - L <= 2 then generate a sequence of assignments when we are
1314 -- processing the bottom most aggregate and it contains scalar
1317 elsif No
(Next_Index
(Index
))
1318 and then Scalar_Comp
1319 and then Local_Compile_Time_Known_Value
(L
)
1320 and then Local_Compile_Time_Known_Value
(H
)
1321 and then Local_Expr_Value
(H
) - Local_Expr_Value
(L
) <= 2
1324 Append_List_To
(S
, Gen_Assign
(New_Copy_Tree
(L
), Expr
));
1325 Append_List_To
(S
, Gen_Assign
(Add
(1, To
=> L
), Expr
));
1327 if Local_Expr_Value
(H
) - Local_Expr_Value
(L
) = 2 then
1328 Append_List_To
(S
, Gen_Assign
(Add
(2, To
=> L
), Expr
));
1334 -- Otherwise construct the loop, starting with the loop index L_J
1336 L_J
:= Make_Temporary
(Loc
, 'J', L
);
1338 -- Construct "L .. H" in Index_Base. We use a qualified expression
1339 -- for the bound to convert to the index base, but we don't need
1340 -- to do that if we already have the base type at hand.
1342 if Etype
(L
) = Index_Base
then
1346 Make_Qualified_Expression
(Loc
,
1347 Subtype_Mark
=> Index_Base_Name
,
1351 if Etype
(H
) = Index_Base
then
1355 Make_Qualified_Expression
(Loc
,
1356 Subtype_Mark
=> Index_Base_Name
,
1365 -- Construct "for L_J in Index_Base range L .. H"
1367 L_Iteration_Scheme
:=
1368 Make_Iteration_Scheme
1370 Loop_Parameter_Specification
=>
1371 Make_Loop_Parameter_Specification
1373 Defining_Identifier
=> L_J
,
1374 Discrete_Subtype_Definition
=> L_Range
));
1376 -- Construct the statements to execute in the loop body
1378 L_Body
:= Gen_Assign
(New_Reference_To
(L_J
, Loc
), Expr
);
1380 -- Construct the final loop
1382 Append_To
(S
, Make_Implicit_Loop_Statement
1384 Identifier
=> Empty
,
1385 Iteration_Scheme
=> L_Iteration_Scheme
,
1386 Statements
=> L_Body
));
1388 -- A small optimization: if the aggregate is initialized with a box
1389 -- and the component type has no initialization procedure, remove the
1390 -- useless empty loop.
1392 if Nkind
(First
(S
)) = N_Loop_Statement
1393 and then Is_Empty_List
(Statements
(First
(S
)))
1395 return New_List
(Make_Null_Statement
(Loc
));
1405 -- The code built is
1407 -- W_J : Index_Base := L;
1408 -- while W_J < H loop
1409 -- W_J := Index_Base'Succ (W);
1413 function Gen_While
(L
, H
: Node_Id
; Expr
: Node_Id
) return List_Id
is
1417 -- W_J : Base_Type := L;
1419 W_Iteration_Scheme
: Node_Id
;
1422 W_Index_Succ
: Node_Id
;
1423 -- Index_Base'Succ (J)
1425 W_Increment
: Node_Id
;
1426 -- W_J := Index_Base'Succ (W)
1428 W_Body
: constant List_Id
:= New_List
;
1429 -- The statements to execute in the loop
1431 S
: constant List_Id
:= New_List
;
1432 -- list of statement
1435 -- If loop bounds define an empty range or are equal return null
1437 if Empty_Range
(L
, H
) or else Equal
(L
, H
) then
1438 Append_To
(S
, Make_Null_Statement
(Loc
));
1442 -- Build the decl of W_J
1444 W_J
:= Make_Temporary
(Loc
, 'J', L
);
1446 Make_Object_Declaration
1448 Defining_Identifier
=> W_J
,
1449 Object_Definition
=> Index_Base_Name
,
1452 -- Theoretically we should do a New_Copy_Tree (L) here, but we know
1453 -- that in this particular case L is a fresh Expr generated by
1454 -- Add which we are the only ones to use.
1456 Append_To
(S
, W_Decl
);
1458 -- Construct " while W_J < H"
1460 W_Iteration_Scheme
:=
1461 Make_Iteration_Scheme
1463 Condition
=> Make_Op_Lt
1465 Left_Opnd
=> New_Reference_To
(W_J
, Loc
),
1466 Right_Opnd
=> New_Copy_Tree
(H
)));
1468 -- Construct the statements to execute in the loop body
1471 Make_Attribute_Reference
1473 Prefix
=> Index_Base_Name
,
1474 Attribute_Name
=> Name_Succ
,
1475 Expressions
=> New_List
(New_Reference_To
(W_J
, Loc
)));
1478 Make_OK_Assignment_Statement
1480 Name
=> New_Reference_To
(W_J
, Loc
),
1481 Expression
=> W_Index_Succ
);
1483 Append_To
(W_Body
, W_Increment
);
1484 Append_List_To
(W_Body
,
1485 Gen_Assign
(New_Reference_To
(W_J
, Loc
), Expr
));
1487 -- Construct the final loop
1489 Append_To
(S
, Make_Implicit_Loop_Statement
1491 Identifier
=> Empty
,
1492 Iteration_Scheme
=> W_Iteration_Scheme
,
1493 Statements
=> W_Body
));
1498 ---------------------
1499 -- Index_Base_Name --
1500 ---------------------
1502 function Index_Base_Name
return Node_Id
is
1504 return New_Reference_To
(Index_Base
, Sloc
(N
));
1505 end Index_Base_Name
;
1507 ------------------------------------
1508 -- Local_Compile_Time_Known_Value --
1509 ------------------------------------
1511 function Local_Compile_Time_Known_Value
(E
: Node_Id
) return Boolean is
1513 return Compile_Time_Known_Value
(E
)
1515 (Nkind
(E
) = N_Attribute_Reference
1516 and then Attribute_Name
(E
) = Name_Val
1517 and then Compile_Time_Known_Value
(First
(Expressions
(E
))));
1518 end Local_Compile_Time_Known_Value
;
1520 ----------------------
1521 -- Local_Expr_Value --
1522 ----------------------
1524 function Local_Expr_Value
(E
: Node_Id
) return Uint
is
1526 if Compile_Time_Known_Value
(E
) then
1527 return Expr_Value
(E
);
1529 return Expr_Value
(First
(Expressions
(E
)));
1531 end Local_Expr_Value
;
1533 -- Build_Array_Aggr_Code Variables
1540 Others_Expr
: Node_Id
:= Empty
;
1541 Others_Box_Present
: Boolean := False;
1543 Aggr_L
: constant Node_Id
:= Low_Bound
(Aggregate_Bounds
(N
));
1544 Aggr_H
: constant Node_Id
:= High_Bound
(Aggregate_Bounds
(N
));
1545 -- The aggregate bounds of this specific sub-aggregate. Note that if
1546 -- the code generated by Build_Array_Aggr_Code is executed then these
1547 -- bounds are OK. Otherwise a Constraint_Error would have been raised.
1549 Aggr_Low
: constant Node_Id
:= Duplicate_Subexpr_No_Checks
(Aggr_L
);
1550 Aggr_High
: constant Node_Id
:= Duplicate_Subexpr_No_Checks
(Aggr_H
);
1551 -- After Duplicate_Subexpr these are side-effect free
1556 Nb_Choices
: Nat
:= 0;
1557 Table
: Case_Table_Type
(1 .. Number_Of_Choices
(N
));
1558 -- Used to sort all the different choice values
1561 -- Number of elements in the positional aggregate
1563 New_Code
: constant List_Id
:= New_List
;
1565 -- Start of processing for Build_Array_Aggr_Code
1568 -- First before we start, a special case. if we have a bit packed
1569 -- array represented as a modular type, then clear the value to
1570 -- zero first, to ensure that unused bits are properly cleared.
1575 and then Is_Bit_Packed_Array
(Typ
)
1576 and then Is_Modular_Integer_Type
(Packed_Array_Type
(Typ
))
1578 Append_To
(New_Code
,
1579 Make_Assignment_Statement
(Loc
,
1580 Name
=> New_Copy_Tree
(Into
),
1582 Unchecked_Convert_To
(Typ
,
1583 Make_Integer_Literal
(Loc
, Uint_0
))));
1586 -- If the component type contains tasks, we need to build a Master
1587 -- entity in the current scope, because it will be needed if build-
1588 -- in-place functions are called in the expanded code.
1590 if Nkind
(Parent
(N
)) = N_Object_Declaration
1591 and then Has_Task
(Typ
)
1593 Build_Master_Entity
(Defining_Identifier
(Parent
(N
)));
1596 -- STEP 1: Process component associations
1598 -- For those associations that may generate a loop, initialize
1599 -- Loop_Actions to collect inserted actions that may be crated.
1601 -- Skip this if no component associations
1603 if No
(Expressions
(N
)) then
1605 -- STEP 1 (a): Sort the discrete choices
1607 Assoc
:= First
(Component_Associations
(N
));
1608 while Present
(Assoc
) loop
1609 Choice
:= First
(Choices
(Assoc
));
1610 while Present
(Choice
) loop
1611 if Nkind
(Choice
) = N_Others_Choice
then
1612 Set_Loop_Actions
(Assoc
, New_List
);
1614 if Box_Present
(Assoc
) then
1615 Others_Box_Present
:= True;
1617 Others_Expr
:= Expression
(Assoc
);
1622 Get_Index_Bounds
(Choice
, Low
, High
);
1625 Set_Loop_Actions
(Assoc
, New_List
);
1628 Nb_Choices
:= Nb_Choices
+ 1;
1629 if Box_Present
(Assoc
) then
1630 Table
(Nb_Choices
) := (Choice_Lo
=> Low
,
1632 Choice_Node
=> Empty
);
1634 Table
(Nb_Choices
) := (Choice_Lo
=> Low
,
1636 Choice_Node
=> Expression
(Assoc
));
1644 -- If there is more than one set of choices these must be static
1645 -- and we can therefore sort them. Remember that Nb_Choices does not
1646 -- account for an others choice.
1648 if Nb_Choices
> 1 then
1649 Sort_Case_Table
(Table
);
1652 -- STEP 1 (b): take care of the whole set of discrete choices
1654 for J
in 1 .. Nb_Choices
loop
1655 Low
:= Table
(J
).Choice_Lo
;
1656 High
:= Table
(J
).Choice_Hi
;
1657 Expr
:= Table
(J
).Choice_Node
;
1658 Append_List
(Gen_Loop
(Low
, High
, Expr
), To
=> New_Code
);
1661 -- STEP 1 (c): generate the remaining loops to cover others choice
1662 -- We don't need to generate loops over empty gaps, but if there is
1663 -- a single empty range we must analyze the expression for semantics
1665 if Present
(Others_Expr
) or else Others_Box_Present
then
1667 First
: Boolean := True;
1670 for J
in 0 .. Nb_Choices
loop
1674 Low
:= Add
(1, To
=> Table
(J
).Choice_Hi
);
1677 if J
= Nb_Choices
then
1680 High
:= Add
(-1, To
=> Table
(J
+ 1).Choice_Lo
);
1683 -- If this is an expansion within an init proc, make
1684 -- sure that discriminant references are replaced by
1685 -- the corresponding discriminal.
1687 if Inside_Init_Proc
then
1688 if Is_Entity_Name
(Low
)
1689 and then Ekind
(Entity
(Low
)) = E_Discriminant
1691 Set_Entity
(Low
, Discriminal
(Entity
(Low
)));
1694 if Is_Entity_Name
(High
)
1695 and then Ekind
(Entity
(High
)) = E_Discriminant
1697 Set_Entity
(High
, Discriminal
(Entity
(High
)));
1702 or else not Empty_Range
(Low
, High
)
1706 (Gen_Loop
(Low
, High
, Others_Expr
), To
=> New_Code
);
1712 -- STEP 2: Process positional components
1715 -- STEP 2 (a): Generate the assignments for each positional element
1716 -- Note that here we have to use Aggr_L rather than Aggr_Low because
1717 -- Aggr_L is analyzed and Add wants an analyzed expression.
1719 Expr
:= First
(Expressions
(N
));
1721 while Present
(Expr
) loop
1722 Nb_Elements
:= Nb_Elements
+ 1;
1723 Append_List
(Gen_Assign
(Add
(Nb_Elements
, To
=> Aggr_L
), Expr
),
1728 -- STEP 2 (b): Generate final loop if an others choice is present
1729 -- Here Nb_Elements gives the offset of the last positional element.
1731 if Present
(Component_Associations
(N
)) then
1732 Assoc
:= Last
(Component_Associations
(N
));
1734 -- Ada 2005 (AI-287)
1736 if Box_Present
(Assoc
) then
1737 Append_List
(Gen_While
(Add
(Nb_Elements
, To
=> Aggr_L
),
1742 Expr
:= Expression
(Assoc
);
1744 Append_List
(Gen_While
(Add
(Nb_Elements
, To
=> Aggr_L
),
1753 end Build_Array_Aggr_Code
;
1755 ----------------------------
1756 -- Build_Record_Aggr_Code --
1757 ----------------------------
1759 function Build_Record_Aggr_Code
1762 Lhs
: Node_Id
) return List_Id
1764 Loc
: constant Source_Ptr
:= Sloc
(N
);
1765 L
: constant List_Id
:= New_List
;
1766 N_Typ
: constant Entity_Id
:= Etype
(N
);
1772 Comp_Type
: Entity_Id
;
1773 Selector
: Entity_Id
;
1774 Comp_Expr
: Node_Id
;
1777 -- If this is an internal aggregate, the External_Final_List is an
1778 -- expression for the controller record of the enclosing type.
1780 -- If the current aggregate has several controlled components, this
1781 -- expression will appear in several calls to attach to the finali-
1782 -- zation list, and it must not be shared.
1784 Ancestor_Is_Expression
: Boolean := False;
1785 Ancestor_Is_Subtype_Mark
: Boolean := False;
1787 Init_Typ
: Entity_Id
:= Empty
;
1789 Finalization_Done
: Boolean := False;
1790 -- True if Generate_Finalization_Actions has already been called; calls
1791 -- after the first do nothing.
1793 function Ancestor_Discriminant_Value
(Disc
: Entity_Id
) return Node_Id
;
1794 -- Returns the value that the given discriminant of an ancestor type
1795 -- should receive (in the absence of a conflict with the value provided
1796 -- by an ancestor part of an extension aggregate).
1798 procedure Check_Ancestor_Discriminants
(Anc_Typ
: Entity_Id
);
1799 -- Check that each of the discriminant values defined by the ancestor
1800 -- part of an extension aggregate match the corresponding values
1801 -- provided by either an association of the aggregate or by the
1802 -- constraint imposed by a parent type (RM95-4.3.2(8)).
1804 function Compatible_Int_Bounds
1805 (Agg_Bounds
: Node_Id
;
1806 Typ_Bounds
: Node_Id
) return Boolean;
1807 -- Return true if Agg_Bounds are equal or within Typ_Bounds. It is
1808 -- assumed that both bounds are integer ranges.
1810 procedure Generate_Finalization_Actions
;
1811 -- Deal with the various controlled type data structure initializations
1812 -- (but only if it hasn't been done already).
1814 function Get_Constraint_Association
(T
: Entity_Id
) return Node_Id
;
1815 -- Returns the first discriminant association in the constraint
1816 -- associated with T, if any, otherwise returns Empty.
1818 procedure Init_Hidden_Discriminants
(Typ
: Entity_Id
; List
: List_Id
);
1819 -- If Typ is derived, and constrains discriminants of the parent type,
1820 -- these discriminants are not components of the aggregate, and must be
1821 -- initialized. The assignments are appended to List.
1823 function Is_Int_Range_Bounds
(Bounds
: Node_Id
) return Boolean;
1824 -- Check whether Bounds is a range node and its lower and higher bounds
1825 -- are integers literals.
1827 ---------------------------------
1828 -- Ancestor_Discriminant_Value --
1829 ---------------------------------
1831 function Ancestor_Discriminant_Value
(Disc
: Entity_Id
) return Node_Id
is
1833 Assoc_Elmt
: Elmt_Id
;
1834 Aggr_Comp
: Entity_Id
;
1835 Corresp_Disc
: Entity_Id
;
1836 Current_Typ
: Entity_Id
:= Base_Type
(Typ
);
1837 Parent_Typ
: Entity_Id
;
1838 Parent_Disc
: Entity_Id
;
1839 Save_Assoc
: Node_Id
:= Empty
;
1842 -- First check any discriminant associations to see if any of them
1843 -- provide a value for the discriminant.
1845 if Present
(Discriminant_Specifications
(Parent
(Current_Typ
))) then
1846 Assoc
:= First
(Component_Associations
(N
));
1847 while Present
(Assoc
) loop
1848 Aggr_Comp
:= Entity
(First
(Choices
(Assoc
)));
1850 if Ekind
(Aggr_Comp
) = E_Discriminant
then
1851 Save_Assoc
:= Expression
(Assoc
);
1853 Corresp_Disc
:= Corresponding_Discriminant
(Aggr_Comp
);
1854 while Present
(Corresp_Disc
) loop
1856 -- If found a corresponding discriminant then return the
1857 -- value given in the aggregate. (Note: this is not
1858 -- correct in the presence of side effects. ???)
1860 if Disc
= Corresp_Disc
then
1861 return Duplicate_Subexpr
(Expression
(Assoc
));
1865 Corresponding_Discriminant
(Corresp_Disc
);
1873 -- No match found in aggregate, so chain up parent types to find
1874 -- a constraint that defines the value of the discriminant.
1876 Parent_Typ
:= Etype
(Current_Typ
);
1877 while Current_Typ
/= Parent_Typ
loop
1878 if Has_Discriminants
(Parent_Typ
)
1879 and then not Has_Unknown_Discriminants
(Parent_Typ
)
1881 Parent_Disc
:= First_Discriminant
(Parent_Typ
);
1883 -- We either get the association from the subtype indication
1884 -- of the type definition itself, or from the discriminant
1885 -- constraint associated with the type entity (which is
1886 -- preferable, but it's not always present ???)
1888 if Is_Empty_Elmt_List
(
1889 Discriminant_Constraint
(Current_Typ
))
1891 Assoc
:= Get_Constraint_Association
(Current_Typ
);
1892 Assoc_Elmt
:= No_Elmt
;
1895 First_Elmt
(Discriminant_Constraint
(Current_Typ
));
1896 Assoc
:= Node
(Assoc_Elmt
);
1899 -- Traverse the discriminants of the parent type looking
1900 -- for one that corresponds.
1902 while Present
(Parent_Disc
) and then Present
(Assoc
) loop
1903 Corresp_Disc
:= Parent_Disc
;
1904 while Present
(Corresp_Disc
)
1905 and then Disc
/= Corresp_Disc
1908 Corresponding_Discriminant
(Corresp_Disc
);
1911 if Disc
= Corresp_Disc
then
1912 if Nkind
(Assoc
) = N_Discriminant_Association
then
1913 Assoc
:= Expression
(Assoc
);
1916 -- If the located association directly denotes a
1917 -- discriminant, then use the value of a saved
1918 -- association of the aggregate. This is a kludge to
1919 -- handle certain cases involving multiple discriminants
1920 -- mapped to a single discriminant of a descendant. It's
1921 -- not clear how to locate the appropriate discriminant
1922 -- value for such cases. ???
1924 if Is_Entity_Name
(Assoc
)
1925 and then Ekind
(Entity
(Assoc
)) = E_Discriminant
1927 Assoc
:= Save_Assoc
;
1930 return Duplicate_Subexpr
(Assoc
);
1933 Next_Discriminant
(Parent_Disc
);
1935 if No
(Assoc_Elmt
) then
1938 Next_Elmt
(Assoc_Elmt
);
1939 if Present
(Assoc_Elmt
) then
1940 Assoc
:= Node
(Assoc_Elmt
);
1948 Current_Typ
:= Parent_Typ
;
1949 Parent_Typ
:= Etype
(Current_Typ
);
1952 -- In some cases there's no ancestor value to locate (such as
1953 -- when an ancestor part given by an expression defines the
1954 -- discriminant value).
1957 end Ancestor_Discriminant_Value
;
1959 ----------------------------------
1960 -- Check_Ancestor_Discriminants --
1961 ----------------------------------
1963 procedure Check_Ancestor_Discriminants
(Anc_Typ
: Entity_Id
) is
1965 Disc_Value
: Node_Id
;
1969 Discr
:= First_Discriminant
(Base_Type
(Anc_Typ
));
1970 while Present
(Discr
) loop
1971 Disc_Value
:= Ancestor_Discriminant_Value
(Discr
);
1973 if Present
(Disc_Value
) then
1974 Cond
:= Make_Op_Ne
(Loc
,
1976 Make_Selected_Component
(Loc
,
1977 Prefix
=> New_Copy_Tree
(Target
),
1978 Selector_Name
=> New_Occurrence_Of
(Discr
, Loc
)),
1979 Right_Opnd
=> Disc_Value
);
1982 Make_Raise_Constraint_Error
(Loc
,
1984 Reason
=> CE_Discriminant_Check_Failed
));
1987 Next_Discriminant
(Discr
);
1989 end Check_Ancestor_Discriminants
;
1991 ---------------------------
1992 -- Compatible_Int_Bounds --
1993 ---------------------------
1995 function Compatible_Int_Bounds
1996 (Agg_Bounds
: Node_Id
;
1997 Typ_Bounds
: Node_Id
) return Boolean
1999 Agg_Lo
: constant Uint
:= Intval
(Low_Bound
(Agg_Bounds
));
2000 Agg_Hi
: constant Uint
:= Intval
(High_Bound
(Agg_Bounds
));
2001 Typ_Lo
: constant Uint
:= Intval
(Low_Bound
(Typ_Bounds
));
2002 Typ_Hi
: constant Uint
:= Intval
(High_Bound
(Typ_Bounds
));
2004 return Typ_Lo
<= Agg_Lo
and then Agg_Hi
<= Typ_Hi
;
2005 end Compatible_Int_Bounds
;
2007 --------------------------------
2008 -- Get_Constraint_Association --
2009 --------------------------------
2011 function Get_Constraint_Association
(T
: Entity_Id
) return Node_Id
is
2018 -- Handle private types in instances
2021 and then Is_Private_Type
(Typ
)
2022 and then Present
(Full_View
(Typ
))
2024 Typ
:= Full_View
(Typ
);
2027 Indic
:= Subtype_Indication
(Type_Definition
(Parent
(Typ
)));
2029 -- ??? Also need to cover case of a type mark denoting a subtype
2032 if Nkind
(Indic
) = N_Subtype_Indication
2033 and then Present
(Constraint
(Indic
))
2035 return First
(Constraints
(Constraint
(Indic
)));
2039 end Get_Constraint_Association
;
2041 -------------------------------
2042 -- Init_Hidden_Discriminants --
2043 -------------------------------
2045 procedure Init_Hidden_Discriminants
(Typ
: Entity_Id
; List
: List_Id
) is
2047 Parent_Type
: Entity_Id
;
2049 Discr_Val
: Elmt_Id
;
2052 Btype
:= Base_Type
(Typ
);
2053 while Is_Derived_Type
(Btype
)
2054 and then Present
(Stored_Constraint
(Btype
))
2056 Parent_Type
:= Etype
(Btype
);
2058 Disc
:= First_Discriminant
(Parent_Type
);
2059 Discr_Val
:= First_Elmt
(Stored_Constraint
(Base_Type
(Typ
)));
2060 while Present
(Discr_Val
) loop
2062 -- Only those discriminants of the parent that are not
2063 -- renamed by discriminants of the derived type need to
2064 -- be added explicitly.
2066 if not Is_Entity_Name
(Node
(Discr_Val
))
2067 or else Ekind
(Entity
(Node
(Discr_Val
))) /= E_Discriminant
2070 Make_Selected_Component
(Loc
,
2071 Prefix
=> New_Copy_Tree
(Target
),
2072 Selector_Name
=> New_Occurrence_Of
(Disc
, Loc
));
2075 Make_OK_Assignment_Statement
(Loc
,
2077 Expression
=> New_Copy_Tree
(Node
(Discr_Val
)));
2079 Set_No_Ctrl_Actions
(Instr
);
2080 Append_To
(List
, Instr
);
2083 Next_Discriminant
(Disc
);
2084 Next_Elmt
(Discr_Val
);
2087 Btype
:= Base_Type
(Parent_Type
);
2089 end Init_Hidden_Discriminants
;
2091 -------------------------
2092 -- Is_Int_Range_Bounds --
2093 -------------------------
2095 function Is_Int_Range_Bounds
(Bounds
: Node_Id
) return Boolean is
2097 return Nkind
(Bounds
) = N_Range
2098 and then Nkind
(Low_Bound
(Bounds
)) = N_Integer_Literal
2099 and then Nkind
(High_Bound
(Bounds
)) = N_Integer_Literal
;
2100 end Is_Int_Range_Bounds
;
2102 -----------------------------------
2103 -- Generate_Finalization_Actions --
2104 -----------------------------------
2106 procedure Generate_Finalization_Actions
is
2108 -- Do the work only the first time this is called
2110 if Finalization_Done
then
2114 Finalization_Done
:= True;
2116 -- Determine the external finalization list. It is either the
2117 -- finalization list of the outer-scope or the one coming from
2118 -- an outer aggregate. When the target is not a temporary, the
2119 -- proper scope is the scope of the target rather than the
2120 -- potentially transient current scope.
2122 if Is_Controlled
(Typ
)
2123 and then Ancestor_Is_Subtype_Mark
2125 Ref
:= Convert_To
(Init_Typ
, New_Copy_Tree
(Target
));
2126 Set_Assignment_OK
(Ref
);
2129 Make_Procedure_Call_Statement
(Loc
,
2132 (Find_Prim_Op
(Init_Typ
, Name_Initialize
), Loc
),
2133 Parameter_Associations
=> New_List
(New_Copy_Tree
(Ref
))));
2135 end Generate_Finalization_Actions
;
2137 function Rewrite_Discriminant
(Expr
: Node_Id
) return Traverse_Result
;
2138 -- If default expression of a component mentions a discriminant of the
2139 -- type, it must be rewritten as the discriminant of the target object.
2141 function Replace_Type
(Expr
: Node_Id
) return Traverse_Result
;
2142 -- If the aggregate contains a self-reference, traverse each expression
2143 -- to replace a possible self-reference with a reference to the proper
2144 -- component of the target of the assignment.
2146 --------------------------
2147 -- Rewrite_Discriminant --
2148 --------------------------
2150 function Rewrite_Discriminant
(Expr
: Node_Id
) return Traverse_Result
is
2152 if Is_Entity_Name
(Expr
)
2153 and then Present
(Entity
(Expr
))
2154 and then Ekind
(Entity
(Expr
)) = E_In_Parameter
2155 and then Present
(Discriminal_Link
(Entity
(Expr
)))
2156 and then Scope
(Discriminal_Link
(Entity
(Expr
)))
2157 = Base_Type
(Etype
(N
))
2160 Make_Selected_Component
(Loc
,
2161 Prefix
=> New_Copy_Tree
(Lhs
),
2162 Selector_Name
=> Make_Identifier
(Loc
, Chars
(Expr
))));
2165 end Rewrite_Discriminant
;
2171 function Replace_Type
(Expr
: Node_Id
) return Traverse_Result
is
2173 -- Note regarding the Root_Type test below: Aggregate components for
2174 -- self-referential types include attribute references to the current
2175 -- instance, of the form: Typ'access, etc.. These references are
2176 -- rewritten as references to the target of the aggregate: the
2177 -- left-hand side of an assignment, the entity in a declaration,
2178 -- or a temporary. Without this test, we would improperly extended
2179 -- this rewriting to attribute references whose prefix was not the
2180 -- type of the aggregate.
2182 if Nkind
(Expr
) = N_Attribute_Reference
2183 and then Is_Entity_Name
(Prefix
(Expr
))
2184 and then Is_Type
(Entity
(Prefix
(Expr
)))
2185 and then Root_Type
(Etype
(N
)) = Root_Type
(Entity
(Prefix
(Expr
)))
2187 if Is_Entity_Name
(Lhs
) then
2188 Rewrite
(Prefix
(Expr
),
2189 New_Occurrence_Of
(Entity
(Lhs
), Loc
));
2191 elsif Nkind
(Lhs
) = N_Selected_Component
then
2193 Make_Attribute_Reference
(Loc
,
2194 Attribute_Name
=> Name_Unrestricted_Access
,
2195 Prefix
=> New_Copy_Tree
(Lhs
)));
2196 Set_Analyzed
(Parent
(Expr
), False);
2200 Make_Attribute_Reference
(Loc
,
2201 Attribute_Name
=> Name_Unrestricted_Access
,
2202 Prefix
=> New_Copy_Tree
(Lhs
)));
2203 Set_Analyzed
(Parent
(Expr
), False);
2210 procedure Replace_Self_Reference
is
2211 new Traverse_Proc
(Replace_Type
);
2213 procedure Replace_Discriminants
is
2214 new Traverse_Proc
(Rewrite_Discriminant
);
2216 -- Start of processing for Build_Record_Aggr_Code
2219 if Has_Self_Reference
(N
) then
2220 Replace_Self_Reference
(N
);
2223 -- If the target of the aggregate is class-wide, we must convert it
2224 -- to the actual type of the aggregate, so that the proper components
2225 -- are visible. We know already that the types are compatible.
2227 if Present
(Etype
(Lhs
))
2228 and then Is_Class_Wide_Type
(Etype
(Lhs
))
2230 Target
:= Unchecked_Convert_To
(Typ
, Lhs
);
2235 -- Deal with the ancestor part of extension aggregates or with the
2236 -- discriminants of the root type.
2238 if Nkind
(N
) = N_Extension_Aggregate
then
2240 Ancestor
: constant Node_Id
:= Ancestor_Part
(N
);
2244 -- If the ancestor part is a subtype mark "T", we generate
2246 -- init-proc (T (tmp)); if T is constrained and
2247 -- init-proc (S (tmp)); where S applies an appropriate
2248 -- constraint if T is unconstrained
2250 if Is_Entity_Name
(Ancestor
)
2251 and then Is_Type
(Entity
(Ancestor
))
2253 Ancestor_Is_Subtype_Mark
:= True;
2255 if Is_Constrained
(Entity
(Ancestor
)) then
2256 Init_Typ
:= Entity
(Ancestor
);
2258 -- For an ancestor part given by an unconstrained type mark,
2259 -- create a subtype constrained by appropriate corresponding
2260 -- discriminant values coming from either associations of the
2261 -- aggregate or a constraint on a parent type. The subtype will
2262 -- be used to generate the correct default value for the
2265 elsif Has_Discriminants
(Entity
(Ancestor
)) then
2267 Anc_Typ
: constant Entity_Id
:= Entity
(Ancestor
);
2268 Anc_Constr
: constant List_Id
:= New_List
;
2269 Discrim
: Entity_Id
;
2270 Disc_Value
: Node_Id
;
2271 New_Indic
: Node_Id
;
2272 Subt_Decl
: Node_Id
;
2275 Discrim
:= First_Discriminant
(Anc_Typ
);
2276 while Present
(Discrim
) loop
2277 Disc_Value
:= Ancestor_Discriminant_Value
(Discrim
);
2278 Append_To
(Anc_Constr
, Disc_Value
);
2279 Next_Discriminant
(Discrim
);
2283 Make_Subtype_Indication
(Loc
,
2284 Subtype_Mark
=> New_Occurrence_Of
(Anc_Typ
, Loc
),
2286 Make_Index_Or_Discriminant_Constraint
(Loc
,
2287 Constraints
=> Anc_Constr
));
2289 Init_Typ
:= Create_Itype
(Ekind
(Anc_Typ
), N
);
2292 Make_Subtype_Declaration
(Loc
,
2293 Defining_Identifier
=> Init_Typ
,
2294 Subtype_Indication
=> New_Indic
);
2296 -- Itypes must be analyzed with checks off Declaration
2297 -- must have a parent for proper handling of subsidiary
2300 Set_Parent
(Subt_Decl
, N
);
2301 Analyze
(Subt_Decl
, Suppress
=> All_Checks
);
2305 Ref
:= Convert_To
(Init_Typ
, New_Copy_Tree
(Target
));
2306 Set_Assignment_OK
(Ref
);
2308 if not Is_Interface
(Init_Typ
) then
2310 Build_Initialization_Call
(Loc
,
2313 In_Init_Proc
=> Within_Init_Proc
,
2314 With_Default_Init
=> Has_Default_Init_Comps
(N
)
2316 Has_Task
(Base_Type
(Init_Typ
))));
2318 if Is_Constrained
(Entity
(Ancestor
))
2319 and then Has_Discriminants
(Entity
(Ancestor
))
2321 Check_Ancestor_Discriminants
(Entity
(Ancestor
));
2325 -- Handle calls to C++ constructors
2327 elsif Is_CPP_Constructor_Call
(Ancestor
) then
2328 Init_Typ
:= Etype
(Ancestor
);
2329 Ref
:= Convert_To
(Init_Typ
, New_Copy_Tree
(Target
));
2330 Set_Assignment_OK
(Ref
);
2333 Build_Initialization_Call
(Loc
,
2336 In_Init_Proc
=> Within_Init_Proc
,
2337 With_Default_Init
=> Has_Default_Init_Comps
(N
),
2338 Constructor_Ref
=> Ancestor
));
2340 -- Ada 2005 (AI-287): If the ancestor part is an aggregate of
2341 -- limited type, a recursive call expands the ancestor. Note that
2342 -- in the limited case, the ancestor part must be either a
2343 -- function call (possibly qualified, or wrapped in an unchecked
2344 -- conversion) or aggregate (definitely qualified).
2345 -- The ancestor part can also be a function call (that may be
2346 -- transformed into an explicit dereference) or a qualification
2349 elsif Is_Limited_Type
(Etype
(Ancestor
))
2350 and then Nkind_In
(Unqualify
(Ancestor
), N_Aggregate
,
2351 N_Extension_Aggregate
)
2353 Ancestor_Is_Expression
:= True;
2355 -- Set up finalization data for enclosing record, because
2356 -- controlled subcomponents of the ancestor part will be
2359 Generate_Finalization_Actions
;
2362 Build_Record_Aggr_Code
2363 (N
=> Unqualify
(Ancestor
),
2364 Typ
=> Etype
(Unqualify
(Ancestor
)),
2367 -- If the ancestor part is an expression "E", we generate
2371 -- In Ada 2005, this includes the case of a (possibly qualified)
2372 -- limited function call. The assignment will turn into a
2373 -- build-in-place function call (for further details, see
2374 -- Make_Build_In_Place_Call_In_Assignment).
2377 Ancestor_Is_Expression
:= True;
2378 Init_Typ
:= Etype
(Ancestor
);
2380 -- If the ancestor part is an aggregate, force its full
2381 -- expansion, which was delayed.
2383 if Nkind_In
(Unqualify
(Ancestor
), N_Aggregate
,
2384 N_Extension_Aggregate
)
2386 Set_Analyzed
(Ancestor
, False);
2387 Set_Analyzed
(Expression
(Ancestor
), False);
2390 Ref
:= Convert_To
(Init_Typ
, New_Copy_Tree
(Target
));
2391 Set_Assignment_OK
(Ref
);
2393 -- Make the assignment without usual controlled actions since
2394 -- we only want the post adjust but not the pre finalize here
2395 -- Add manual adjust when necessary.
2397 Assign
:= New_List
(
2398 Make_OK_Assignment_Statement
(Loc
,
2400 Expression
=> Ancestor
));
2401 Set_No_Ctrl_Actions
(First
(Assign
));
2403 -- Assign the tag now to make sure that the dispatching call in
2404 -- the subsequent deep_adjust works properly (unless VM_Target,
2405 -- where tags are implicit).
2407 if Tagged_Type_Expansion
then
2409 Make_OK_Assignment_Statement
(Loc
,
2411 Make_Selected_Component
(Loc
,
2412 Prefix
=> New_Copy_Tree
(Target
),
2415 (First_Tag_Component
(Base_Type
(Typ
)), Loc
)),
2418 Unchecked_Convert_To
(RTE
(RE_Tag
),
2421 (Access_Disp_Table
(Base_Type
(Typ
)))),
2424 Set_Assignment_OK
(Name
(Instr
));
2425 Append_To
(Assign
, Instr
);
2427 -- Ada 2005 (AI-251): If tagged type has progenitors we must
2428 -- also initialize tags of the secondary dispatch tables.
2430 if Has_Interfaces
(Base_Type
(Typ
)) then
2432 (Typ
=> Base_Type
(Typ
),
2434 Stmts_List
=> Assign
);
2438 -- Call Adjust manually
2440 if Needs_Finalization
(Etype
(Ancestor
))
2441 and then not Is_Limited_Type
(Etype
(Ancestor
))
2445 Obj_Ref
=> New_Copy_Tree
(Ref
),
2446 Typ
=> Etype
(Ancestor
)));
2450 Make_Unsuppress_Block
(Loc
, Name_Discriminant_Check
, Assign
));
2452 if Has_Discriminants
(Init_Typ
) then
2453 Check_Ancestor_Discriminants
(Init_Typ
);
2458 -- Generate assignments of hidden assignments. If the base type is an
2459 -- unchecked union, the discriminants are unknown to the back-end and
2460 -- absent from a value of the type, so assignments for them are not
2463 if Has_Discriminants
(Typ
)
2464 and then not Is_Unchecked_Union
(Base_Type
(Typ
))
2466 Init_Hidden_Discriminants
(Typ
, L
);
2469 -- Normal case (not an extension aggregate)
2472 -- Generate the discriminant expressions, component by component.
2473 -- If the base type is an unchecked union, the discriminants are
2474 -- unknown to the back-end and absent from a value of the type, so
2475 -- assignments for them are not emitted.
2477 if Has_Discriminants
(Typ
)
2478 and then not Is_Unchecked_Union
(Base_Type
(Typ
))
2480 Init_Hidden_Discriminants
(Typ
, L
);
2482 -- Generate discriminant init values for the visible discriminants
2485 Discriminant
: Entity_Id
;
2486 Discriminant_Value
: Node_Id
;
2489 Discriminant
:= First_Stored_Discriminant
(Typ
);
2490 while Present
(Discriminant
) loop
2492 Make_Selected_Component
(Loc
,
2493 Prefix
=> New_Copy_Tree
(Target
),
2494 Selector_Name
=> New_Occurrence_Of
(Discriminant
, Loc
));
2496 Discriminant_Value
:=
2497 Get_Discriminant_Value
(
2500 Discriminant_Constraint
(N_Typ
));
2503 Make_OK_Assignment_Statement
(Loc
,
2505 Expression
=> New_Copy_Tree
(Discriminant_Value
));
2507 Set_No_Ctrl_Actions
(Instr
);
2508 Append_To
(L
, Instr
);
2510 Next_Stored_Discriminant
(Discriminant
);
2516 -- For CPP types we generate an implicit call to the C++ default
2517 -- constructor to ensure the proper initialization of the _Tag
2520 if Is_CPP_Class
(Root_Type
(Typ
))
2521 and then CPP_Num_Prims
(Typ
) > 0
2523 Invoke_Constructor
: declare
2524 CPP_Parent
: constant Entity_Id
:= Enclosing_CPP_Parent
(Typ
);
2526 procedure Invoke_IC_Proc
(T
: Entity_Id
);
2527 -- Recursive routine used to climb to parents. Required because
2528 -- parents must be initialized before descendants to ensure
2529 -- propagation of inherited C++ slots.
2531 --------------------
2532 -- Invoke_IC_Proc --
2533 --------------------
2535 procedure Invoke_IC_Proc
(T
: Entity_Id
) is
2537 -- Avoid generating extra calls. Initialization required
2538 -- only for types defined from the level of derivation of
2539 -- type of the constructor and the type of the aggregate.
2541 if T
= CPP_Parent
then
2545 Invoke_IC_Proc
(Etype
(T
));
2547 -- Generate call to the IC routine
2549 if Present
(CPP_Init_Proc
(T
)) then
2551 Make_Procedure_Call_Statement
(Loc
,
2552 New_Reference_To
(CPP_Init_Proc
(T
), Loc
)));
2556 -- Start of processing for Invoke_Constructor
2559 -- Implicit invocation of the C++ constructor
2561 if Nkind
(N
) = N_Aggregate
then
2563 Make_Procedure_Call_Statement
(Loc
,
2566 (Base_Init_Proc
(CPP_Parent
), Loc
),
2567 Parameter_Associations
=> New_List
(
2568 Unchecked_Convert_To
(CPP_Parent
,
2569 New_Copy_Tree
(Lhs
)))));
2572 Invoke_IC_Proc
(Typ
);
2573 end Invoke_Constructor
;
2576 -- Generate the assignments, component by component
2578 -- tmp.comp1 := Expr1_From_Aggr;
2579 -- tmp.comp2 := Expr2_From_Aggr;
2582 Comp
:= First
(Component_Associations
(N
));
2583 while Present
(Comp
) loop
2584 Selector
:= Entity
(First
(Choices
(Comp
)));
2588 if Is_CPP_Constructor_Call
(Expression
(Comp
)) then
2590 Build_Initialization_Call
(Loc
,
2591 Id_Ref
=> Make_Selected_Component
(Loc
,
2592 Prefix
=> New_Copy_Tree
(Target
),
2594 New_Occurrence_Of
(Selector
, Loc
)),
2595 Typ
=> Etype
(Selector
),
2597 With_Default_Init
=> True,
2598 Constructor_Ref
=> Expression
(Comp
)));
2600 -- Ada 2005 (AI-287): For each default-initialized component generate
2601 -- a call to the corresponding IP subprogram if available.
2603 elsif Box_Present
(Comp
)
2604 and then Has_Non_Null_Base_Init_Proc
(Etype
(Selector
))
2606 if Ekind
(Selector
) /= E_Discriminant
then
2607 Generate_Finalization_Actions
;
2610 -- Ada 2005 (AI-287): If the component type has tasks then
2611 -- generate the activation chain and master entities (except
2612 -- in case of an allocator because in that case these entities
2613 -- are generated by Build_Task_Allocate_Block_With_Init_Stmts).
2616 Ctype
: constant Entity_Id
:= Etype
(Selector
);
2617 Inside_Allocator
: Boolean := False;
2618 P
: Node_Id
:= Parent
(N
);
2621 if Is_Task_Type
(Ctype
) or else Has_Task
(Ctype
) then
2622 while Present
(P
) loop
2623 if Nkind
(P
) = N_Allocator
then
2624 Inside_Allocator
:= True;
2631 if not Inside_Init_Proc
and not Inside_Allocator
then
2632 Build_Activation_Chain_Entity
(N
);
2638 Build_Initialization_Call
(Loc
,
2639 Id_Ref
=> Make_Selected_Component
(Loc
,
2640 Prefix
=> New_Copy_Tree
(Target
),
2642 New_Occurrence_Of
(Selector
, Loc
)),
2643 Typ
=> Etype
(Selector
),
2645 With_Default_Init
=> True));
2647 -- Prepare for component assignment
2649 elsif Ekind
(Selector
) /= E_Discriminant
2650 or else Nkind
(N
) = N_Extension_Aggregate
2652 -- All the discriminants have now been assigned
2654 -- This is now a good moment to initialize and attach all the
2655 -- controllers. Their position may depend on the discriminants.
2657 if Ekind
(Selector
) /= E_Discriminant
then
2658 Generate_Finalization_Actions
;
2661 Comp_Type
:= Underlying_Type
(Etype
(Selector
));
2663 Make_Selected_Component
(Loc
,
2664 Prefix
=> New_Copy_Tree
(Target
),
2665 Selector_Name
=> New_Occurrence_Of
(Selector
, Loc
));
2667 if Nkind
(Expression
(Comp
)) = N_Qualified_Expression
then
2668 Expr_Q
:= Expression
(Expression
(Comp
));
2670 Expr_Q
:= Expression
(Comp
);
2673 -- Now either create the assignment or generate the code for the
2674 -- inner aggregate top-down.
2676 if Is_Delayed_Aggregate
(Expr_Q
) then
2678 -- We have the following case of aggregate nesting inside
2679 -- an object declaration:
2681 -- type Arr_Typ is array (Integer range <>) of ...;
2683 -- type Rec_Typ (...) is record
2684 -- Obj_Arr_Typ : Arr_Typ (A .. B);
2687 -- Obj_Rec_Typ : Rec_Typ := (...,
2688 -- Obj_Arr_Typ => (X => (...), Y => (...)));
2690 -- The length of the ranges of the aggregate and Obj_Add_Typ
2691 -- are equal (B - A = Y - X), but they do not coincide (X /=
2692 -- A and B /= Y). This case requires array sliding which is
2693 -- performed in the following manner:
2695 -- subtype Arr_Sub is Arr_Typ (X .. Y);
2697 -- Temp (X) := (...);
2699 -- Temp (Y) := (...);
2700 -- Obj_Rec_Typ.Obj_Arr_Typ := Temp;
2702 if Ekind
(Comp_Type
) = E_Array_Subtype
2703 and then Is_Int_Range_Bounds
(Aggregate_Bounds
(Expr_Q
))
2704 and then Is_Int_Range_Bounds
(First_Index
(Comp_Type
))
2706 Compatible_Int_Bounds
2707 (Agg_Bounds
=> Aggregate_Bounds
(Expr_Q
),
2708 Typ_Bounds
=> First_Index
(Comp_Type
))
2710 -- Create the array subtype with bounds equal to those of
2711 -- the corresponding aggregate.
2714 SubE
: constant Entity_Id
:= Make_Temporary
(Loc
, 'T');
2716 SubD
: constant Node_Id
:=
2717 Make_Subtype_Declaration
(Loc
,
2718 Defining_Identifier
=> SubE
,
2719 Subtype_Indication
=>
2720 Make_Subtype_Indication
(Loc
,
2722 New_Reference_To
(Etype
(Comp_Type
), Loc
),
2724 Make_Index_Or_Discriminant_Constraint
2726 Constraints
=> New_List
(
2728 (Aggregate_Bounds
(Expr_Q
))))));
2730 -- Create a temporary array of the above subtype which
2731 -- will be used to capture the aggregate assignments.
2733 TmpE
: constant Entity_Id
:= Make_Temporary
(Loc
, 'A', N
);
2735 TmpD
: constant Node_Id
:=
2736 Make_Object_Declaration
(Loc
,
2737 Defining_Identifier
=> TmpE
,
2738 Object_Definition
=> New_Reference_To
(SubE
, Loc
));
2741 Set_No_Initialization
(TmpD
);
2742 Append_To
(L
, SubD
);
2743 Append_To
(L
, TmpD
);
2745 -- Expand aggregate into assignments to the temp array
2748 Late_Expansion
(Expr_Q
, Comp_Type
,
2749 New_Reference_To
(TmpE
, Loc
)));
2754 Make_Assignment_Statement
(Loc
,
2755 Name
=> New_Copy_Tree
(Comp_Expr
),
2756 Expression
=> New_Reference_To
(TmpE
, Loc
)));
2759 -- Normal case (sliding not required)
2763 Late_Expansion
(Expr_Q
, Comp_Type
, Comp_Expr
));
2766 -- Expr_Q is not delayed aggregate
2769 if Has_Discriminants
(Typ
) then
2770 Replace_Discriminants
(Expr_Q
);
2774 Make_OK_Assignment_Statement
(Loc
,
2776 Expression
=> Expr_Q
);
2778 Set_No_Ctrl_Actions
(Instr
);
2779 Append_To
(L
, Instr
);
2781 -- Adjust the tag if tagged (because of possible view
2782 -- conversions), unless compiling for a VM where tags are
2785 -- tmp.comp._tag := comp_typ'tag;
2787 if Is_Tagged_Type
(Comp_Type
)
2788 and then Tagged_Type_Expansion
2791 Make_OK_Assignment_Statement
(Loc
,
2793 Make_Selected_Component
(Loc
,
2794 Prefix
=> New_Copy_Tree
(Comp_Expr
),
2797 (First_Tag_Component
(Comp_Type
), Loc
)),
2800 Unchecked_Convert_To
(RTE
(RE_Tag
),
2802 (Node
(First_Elmt
(Access_Disp_Table
(Comp_Type
))),
2805 Append_To
(L
, Instr
);
2809 -- Adjust (tmp.comp);
2811 if Needs_Finalization
(Comp_Type
)
2812 and then not Is_Limited_Type
(Comp_Type
)
2816 Obj_Ref
=> New_Copy_Tree
(Comp_Expr
),
2823 elsif Ekind
(Selector
) = E_Discriminant
2824 and then Nkind
(N
) /= N_Extension_Aggregate
2825 and then Nkind
(Parent
(N
)) = N_Component_Association
2826 and then Is_Constrained
(Typ
)
2828 -- We must check that the discriminant value imposed by the
2829 -- context is the same as the value given in the subaggregate,
2830 -- because after the expansion into assignments there is no
2831 -- record on which to perform a regular discriminant check.
2838 D_Val
:= First_Elmt
(Discriminant_Constraint
(Typ
));
2839 Disc
:= First_Discriminant
(Typ
);
2840 while Chars
(Disc
) /= Chars
(Selector
) loop
2841 Next_Discriminant
(Disc
);
2845 pragma Assert
(Present
(D_Val
));
2847 -- This check cannot performed for components that are
2848 -- constrained by a current instance, because this is not a
2849 -- value that can be compared with the actual constraint.
2851 if Nkind
(Node
(D_Val
)) /= N_Attribute_Reference
2852 or else not Is_Entity_Name
(Prefix
(Node
(D_Val
)))
2853 or else not Is_Type
(Entity
(Prefix
(Node
(D_Val
))))
2856 Make_Raise_Constraint_Error
(Loc
,
2859 Left_Opnd
=> New_Copy_Tree
(Node
(D_Val
)),
2860 Right_Opnd
=> Expression
(Comp
)),
2861 Reason
=> CE_Discriminant_Check_Failed
));
2864 -- Find self-reference in previous discriminant assignment,
2865 -- and replace with proper expression.
2872 while Present
(Ass
) loop
2873 if Nkind
(Ass
) = N_Assignment_Statement
2874 and then Nkind
(Name
(Ass
)) = N_Selected_Component
2875 and then Chars
(Selector_Name
(Name
(Ass
))) =
2879 (Ass
, New_Copy_Tree
(Expression
(Comp
)));
2892 -- If the type is tagged, the tag needs to be initialized (unless
2893 -- compiling for the Java VM where tags are implicit). It is done
2894 -- late in the initialization process because in some cases, we call
2895 -- the init proc of an ancestor which will not leave out the right tag
2897 if Ancestor_Is_Expression
then
2900 -- For CPP types we generated a call to the C++ default constructor
2901 -- before the components have been initialized to ensure the proper
2902 -- initialization of the _Tag component (see above).
2904 elsif Is_CPP_Class
(Typ
) then
2907 elsif Is_Tagged_Type
(Typ
) and then Tagged_Type_Expansion
then
2909 Make_OK_Assignment_Statement
(Loc
,
2911 Make_Selected_Component
(Loc
,
2912 Prefix
=> New_Copy_Tree
(Target
),
2915 (First_Tag_Component
(Base_Type
(Typ
)), Loc
)),
2918 Unchecked_Convert_To
(RTE
(RE_Tag
),
2920 (Node
(First_Elmt
(Access_Disp_Table
(Base_Type
(Typ
)))),
2923 Append_To
(L
, Instr
);
2925 -- Ada 2005 (AI-251): If the tagged type has been derived from
2926 -- abstract interfaces we must also initialize the tags of the
2927 -- secondary dispatch tables.
2929 if Has_Interfaces
(Base_Type
(Typ
)) then
2931 (Typ
=> Base_Type
(Typ
),
2937 -- If the controllers have not been initialized yet (by lack of non-
2938 -- discriminant components), let's do it now.
2940 Generate_Finalization_Actions
;
2943 end Build_Record_Aggr_Code
;
2945 -------------------------------
2946 -- Convert_Aggr_In_Allocator --
2947 -------------------------------
2949 procedure Convert_Aggr_In_Allocator
2954 Loc
: constant Source_Ptr
:= Sloc
(Aggr
);
2955 Typ
: constant Entity_Id
:= Etype
(Aggr
);
2956 Temp
: constant Entity_Id
:= Defining_Identifier
(Decl
);
2958 Occ
: constant Node_Id
:=
2959 Unchecked_Convert_To
(Typ
,
2960 Make_Explicit_Dereference
(Loc
, New_Reference_To
(Temp
, Loc
)));
2963 if Is_Array_Type
(Typ
) then
2964 Convert_Array_Aggr_In_Allocator
(Decl
, Aggr
, Occ
);
2966 elsif Has_Default_Init_Comps
(Aggr
) then
2968 L
: constant List_Id
:= New_List
;
2969 Init_Stmts
: List_Id
;
2972 Init_Stmts
:= Late_Expansion
(Aggr
, Typ
, Occ
);
2974 if Has_Task
(Typ
) then
2975 Build_Task_Allocate_Block_With_Init_Stmts
(L
, Aggr
, Init_Stmts
);
2976 Insert_Actions
(Alloc
, L
);
2978 Insert_Actions
(Alloc
, Init_Stmts
);
2983 Insert_Actions
(Alloc
, Late_Expansion
(Aggr
, Typ
, Occ
));
2985 end Convert_Aggr_In_Allocator
;
2987 --------------------------------
2988 -- Convert_Aggr_In_Assignment --
2989 --------------------------------
2991 procedure Convert_Aggr_In_Assignment
(N
: Node_Id
) is
2992 Aggr
: Node_Id
:= Expression
(N
);
2993 Typ
: constant Entity_Id
:= Etype
(Aggr
);
2994 Occ
: constant Node_Id
:= New_Copy_Tree
(Name
(N
));
2997 if Nkind
(Aggr
) = N_Qualified_Expression
then
2998 Aggr
:= Expression
(Aggr
);
3001 Insert_Actions_After
(N
, Late_Expansion
(Aggr
, Typ
, Occ
));
3002 end Convert_Aggr_In_Assignment
;
3004 ---------------------------------
3005 -- Convert_Aggr_In_Object_Decl --
3006 ---------------------------------
3008 procedure Convert_Aggr_In_Object_Decl
(N
: Node_Id
) is
3009 Obj
: constant Entity_Id
:= Defining_Identifier
(N
);
3010 Aggr
: Node_Id
:= Expression
(N
);
3011 Loc
: constant Source_Ptr
:= Sloc
(Aggr
);
3012 Typ
: constant Entity_Id
:= Etype
(Aggr
);
3013 Occ
: constant Node_Id
:= New_Occurrence_Of
(Obj
, Loc
);
3015 function Discriminants_Ok
return Boolean;
3016 -- If the object type is constrained, the discriminants in the
3017 -- aggregate must be checked against the discriminants of the subtype.
3018 -- This cannot be done using Apply_Discriminant_Checks because after
3019 -- expansion there is no aggregate left to check.
3021 ----------------------
3022 -- Discriminants_Ok --
3023 ----------------------
3025 function Discriminants_Ok
return Boolean is
3026 Cond
: Node_Id
:= Empty
;
3035 D
:= First_Discriminant
(Typ
);
3036 Disc1
:= First_Elmt
(Discriminant_Constraint
(Typ
));
3037 Disc2
:= First_Elmt
(Discriminant_Constraint
(Etype
(Obj
)));
3038 while Present
(Disc1
) and then Present
(Disc2
) loop
3039 Val1
:= Node
(Disc1
);
3040 Val2
:= Node
(Disc2
);
3042 if not Is_OK_Static_Expression
(Val1
)
3043 or else not Is_OK_Static_Expression
(Val2
)
3045 Check
:= Make_Op_Ne
(Loc
,
3046 Left_Opnd
=> Duplicate_Subexpr
(Val1
),
3047 Right_Opnd
=> Duplicate_Subexpr
(Val2
));
3053 Cond
:= Make_Or_Else
(Loc
,
3055 Right_Opnd
=> Check
);
3058 elsif Expr_Value
(Val1
) /= Expr_Value
(Val2
) then
3059 Apply_Compile_Time_Constraint_Error
(Aggr
,
3060 Msg
=> "incorrect value for discriminant&?",
3061 Reason
=> CE_Discriminant_Check_Failed
,
3066 Next_Discriminant
(D
);
3071 -- If any discriminant constraint is non-static, emit a check
3073 if Present
(Cond
) then
3075 Make_Raise_Constraint_Error
(Loc
,
3077 Reason
=> CE_Discriminant_Check_Failed
));
3081 end Discriminants_Ok
;
3083 -- Start of processing for Convert_Aggr_In_Object_Decl
3086 Set_Assignment_OK
(Occ
);
3088 if Nkind
(Aggr
) = N_Qualified_Expression
then
3089 Aggr
:= Expression
(Aggr
);
3092 if Has_Discriminants
(Typ
)
3093 and then Typ
/= Etype
(Obj
)
3094 and then Is_Constrained
(Etype
(Obj
))
3095 and then not Discriminants_Ok
3100 -- If the context is an extended return statement, it has its own
3101 -- finalization machinery (i.e. works like a transient scope) and
3102 -- we do not want to create an additional one, because objects on
3103 -- the finalization list of the return must be moved to the caller's
3104 -- finalization list to complete the return.
3106 -- However, if the aggregate is limited, it is built in place, and the
3107 -- controlled components are not assigned to intermediate temporaries
3108 -- so there is no need for a transient scope in this case either.
3110 if Requires_Transient_Scope
(Typ
)
3111 and then Ekind
(Current_Scope
) /= E_Return_Statement
3112 and then not Is_Limited_Type
(Typ
)
3114 Establish_Transient_Scope
3117 Is_Controlled
(Typ
) or else Has_Controlled_Component
(Typ
));
3120 Insert_Actions_After
(N
, Late_Expansion
(Aggr
, Typ
, Occ
));
3121 Set_No_Initialization
(N
);
3122 Initialize_Discriminants
(N
, Typ
);
3123 end Convert_Aggr_In_Object_Decl
;
3125 -------------------------------------
3126 -- Convert_Array_Aggr_In_Allocator --
3127 -------------------------------------
3129 procedure Convert_Array_Aggr_In_Allocator
3134 Aggr_Code
: List_Id
;
3135 Typ
: constant Entity_Id
:= Etype
(Aggr
);
3136 Ctyp
: constant Entity_Id
:= Component_Type
(Typ
);
3139 -- The target is an explicit dereference of the allocated object.
3140 -- Generate component assignments to it, as for an aggregate that
3141 -- appears on the right-hand side of an assignment statement.
3144 Build_Array_Aggr_Code
(Aggr
,
3146 Index
=> First_Index
(Typ
),
3148 Scalar_Comp
=> Is_Scalar_Type
(Ctyp
));
3150 Insert_Actions_After
(Decl
, Aggr_Code
);
3151 end Convert_Array_Aggr_In_Allocator
;
3153 ----------------------------
3154 -- Convert_To_Assignments --
3155 ----------------------------
3157 procedure Convert_To_Assignments
(N
: Node_Id
; Typ
: Entity_Id
) is
3158 Loc
: constant Source_Ptr
:= Sloc
(N
);
3163 Target_Expr
: Node_Id
;
3164 Parent_Kind
: Node_Kind
;
3165 Unc_Decl
: Boolean := False;
3166 Parent_Node
: Node_Id
;
3169 pragma Assert
(not Is_Static_Dispatch_Table_Aggregate
(N
));
3170 pragma Assert
(Is_Record_Type
(Typ
));
3172 Parent_Node
:= Parent
(N
);
3173 Parent_Kind
:= Nkind
(Parent_Node
);
3175 if Parent_Kind
= N_Qualified_Expression
then
3177 -- Check if we are in a unconstrained declaration because in this
3178 -- case the current delayed expansion mechanism doesn't work when
3179 -- the declared object size depend on the initializing expr.
3182 Parent_Node
:= Parent
(Parent_Node
);
3183 Parent_Kind
:= Nkind
(Parent_Node
);
3185 if Parent_Kind
= N_Object_Declaration
then
3187 not Is_Entity_Name
(Object_Definition
(Parent_Node
))
3188 or else Has_Discriminants
3189 (Entity
(Object_Definition
(Parent_Node
)))
3190 or else Is_Class_Wide_Type
3191 (Entity
(Object_Definition
(Parent_Node
)));
3196 -- Just set the Delay flag in the cases where the transformation will be
3197 -- done top down from above.
3201 -- Internal aggregate (transformed when expanding the parent)
3203 or else Parent_Kind
= N_Aggregate
3204 or else Parent_Kind
= N_Extension_Aggregate
3205 or else Parent_Kind
= N_Component_Association
3207 -- Allocator (see Convert_Aggr_In_Allocator)
3209 or else Parent_Kind
= N_Allocator
3211 -- Object declaration (see Convert_Aggr_In_Object_Decl)
3213 or else (Parent_Kind
= N_Object_Declaration
and then not Unc_Decl
)
3215 -- Safe assignment (see Convert_Aggr_Assignments). So far only the
3216 -- assignments in init procs are taken into account.
3218 or else (Parent_Kind
= N_Assignment_Statement
3219 and then Inside_Init_Proc
)
3221 -- (Ada 2005) An inherently limited type in a return statement,
3222 -- which will be handled in a build-in-place fashion, and may be
3223 -- rewritten as an extended return and have its own finalization
3224 -- machinery. In the case of a simple return, the aggregate needs
3225 -- to be delayed until the scope for the return statement has been
3226 -- created, so that any finalization chain will be associated with
3227 -- that scope. For extended returns, we delay expansion to avoid the
3228 -- creation of an unwanted transient scope that could result in
3229 -- premature finalization of the return object (which is built in
3230 -- in place within the caller's scope).
3233 (Is_Immutably_Limited_Type
(Typ
)
3235 (Nkind
(Parent
(Parent_Node
)) = N_Extended_Return_Statement
3236 or else Nkind
(Parent_Node
) = N_Simple_Return_Statement
))
3238 Set_Expansion_Delayed
(N
);
3242 if Requires_Transient_Scope
(Typ
) then
3243 Establish_Transient_Scope
3245 Is_Controlled
(Typ
) or else Has_Controlled_Component
(Typ
));
3248 -- If the aggregate is non-limited, create a temporary. If it is limited
3249 -- and the context is an assignment, this is a subaggregate for an
3250 -- enclosing aggregate being expanded. It must be built in place, so use
3251 -- the target of the current assignment.
3253 if Is_Limited_Type
(Typ
)
3254 and then Nkind
(Parent
(N
)) = N_Assignment_Statement
3256 Target_Expr
:= New_Copy_Tree
(Name
(Parent
(N
)));
3257 Insert_Actions
(Parent
(N
),
3258 Build_Record_Aggr_Code
(N
, Typ
, Target_Expr
));
3259 Rewrite
(Parent
(N
), Make_Null_Statement
(Loc
));
3262 Temp
:= Make_Temporary
(Loc
, 'A', N
);
3264 -- If the type inherits unknown discriminants, use the view with
3265 -- known discriminants if available.
3267 if Has_Unknown_Discriminants
(Typ
)
3268 and then Present
(Underlying_Record_View
(Typ
))
3270 T
:= Underlying_Record_View
(Typ
);
3276 Make_Object_Declaration
(Loc
,
3277 Defining_Identifier
=> Temp
,
3278 Object_Definition
=> New_Occurrence_Of
(T
, Loc
));
3280 Set_No_Initialization
(Instr
);
3281 Insert_Action
(N
, Instr
);
3282 Initialize_Discriminants
(Instr
, T
);
3283 Target_Expr
:= New_Occurrence_Of
(Temp
, Loc
);
3284 Insert_Actions
(N
, Build_Record_Aggr_Code
(N
, T
, Target_Expr
));
3285 Rewrite
(N
, New_Occurrence_Of
(Temp
, Loc
));
3286 Analyze_And_Resolve
(N
, T
);
3288 end Convert_To_Assignments
;
3290 ---------------------------
3291 -- Convert_To_Positional --
3292 ---------------------------
3294 procedure Convert_To_Positional
3296 Max_Others_Replicate
: Nat
:= 5;
3297 Handle_Bit_Packed
: Boolean := False)
3299 Typ
: constant Entity_Id
:= Etype
(N
);
3301 Static_Components
: Boolean := True;
3303 procedure Check_Static_Components
;
3304 -- Check whether all components of the aggregate are compile-time known
3305 -- values, and can be passed as is to the back-end without further
3311 Ixb
: Node_Id
) return Boolean;
3312 -- Convert the aggregate into a purely positional form if possible. On
3313 -- entry the bounds of all dimensions are known to be static, and the
3314 -- total number of components is safe enough to expand.
3316 function Is_Flat
(N
: Node_Id
; Dims
: Int
) return Boolean;
3317 -- Return True iff the array N is flat (which is not trivial in the case
3318 -- of multidimensional aggregates).
3320 -----------------------------
3321 -- Check_Static_Components --
3322 -----------------------------
3324 procedure Check_Static_Components
is
3328 Static_Components
:= True;
3330 if Nkind
(N
) = N_String_Literal
then
3333 elsif Present
(Expressions
(N
)) then
3334 Expr
:= First
(Expressions
(N
));
3335 while Present
(Expr
) loop
3336 if Nkind
(Expr
) /= N_Aggregate
3337 or else not Compile_Time_Known_Aggregate
(Expr
)
3338 or else Expansion_Delayed
(Expr
)
3340 Static_Components
:= False;
3348 if Nkind
(N
) = N_Aggregate
3349 and then Present
(Component_Associations
(N
))
3351 Expr
:= First
(Component_Associations
(N
));
3352 while Present
(Expr
) loop
3353 if Nkind_In
(Expression
(Expr
), N_Integer_Literal
,
3358 elsif Is_Entity_Name
(Expression
(Expr
))
3359 and then Present
(Entity
(Expression
(Expr
)))
3360 and then Ekind
(Entity
(Expression
(Expr
))) =
3361 E_Enumeration_Literal
3365 elsif Nkind
(Expression
(Expr
)) /= N_Aggregate
3366 or else not Compile_Time_Known_Aggregate
(Expression
(Expr
))
3367 or else Expansion_Delayed
(Expression
(Expr
))
3369 Static_Components
:= False;
3376 end Check_Static_Components
;
3385 Ixb
: Node_Id
) return Boolean
3387 Loc
: constant Source_Ptr
:= Sloc
(N
);
3388 Blo
: constant Node_Id
:= Type_Low_Bound
(Etype
(Ixb
));
3389 Lo
: constant Node_Id
:= Type_Low_Bound
(Etype
(Ix
));
3390 Hi
: constant Node_Id
:= Type_High_Bound
(Etype
(Ix
));
3394 Others_Present
: Boolean := False;
3397 if Nkind
(Original_Node
(N
)) = N_String_Literal
then
3401 if not Compile_Time_Known_Value
(Lo
)
3402 or else not Compile_Time_Known_Value
(Hi
)
3407 Lov
:= Expr_Value
(Lo
);
3408 Hiv
:= Expr_Value
(Hi
);
3410 -- Check if there is an others choice
3412 if Present
(Component_Associations
(N
)) then
3418 Assoc
:= First
(Component_Associations
(N
));
3419 while Present
(Assoc
) loop
3421 -- If this is a box association, flattening is in general
3422 -- not possible because at this point we cannot tell if the
3423 -- default is static or even exists.
3425 if Box_Present
(Assoc
) then
3429 Choice
:= First
(Choices
(Assoc
));
3431 while Present
(Choice
) loop
3432 if Nkind
(Choice
) = N_Others_Choice
then
3433 Others_Present
:= True;
3444 -- If the low bound is not known at compile time and others is not
3445 -- present we can proceed since the bounds can be obtained from the
3448 -- Note: This case is required in VM platforms since their backends
3449 -- normalize array indexes in the range 0 .. N-1. Hence, if we do
3450 -- not flat an array whose bounds cannot be obtained from the type
3451 -- of the index the backend has no way to properly generate the code.
3452 -- See ACATS c460010 for an example.
3455 or else (not Compile_Time_Known_Value
(Blo
)
3456 and then Others_Present
)
3461 -- Determine if set of alternatives is suitable for conversion and
3462 -- build an array containing the values in sequence.
3465 Vals
: array (UI_To_Int
(Lov
) .. UI_To_Int
(Hiv
))
3466 of Node_Id
:= (others => Empty
);
3467 -- The values in the aggregate sorted appropriately
3470 -- Same data as Vals in list form
3473 -- Used to validate Max_Others_Replicate limit
3476 Num
: Int
:= UI_To_Int
(Lov
);
3482 if Present
(Expressions
(N
)) then
3483 Elmt
:= First
(Expressions
(N
));
3484 while Present
(Elmt
) loop
3485 if Nkind
(Elmt
) = N_Aggregate
3486 and then Present
(Next_Index
(Ix
))
3488 not Flatten
(Elmt
, Next_Index
(Ix
), Next_Index
(Ixb
))
3493 Vals
(Num
) := Relocate_Node
(Elmt
);
3500 if No
(Component_Associations
(N
)) then
3504 Elmt
:= First
(Component_Associations
(N
));
3506 if Nkind
(Expression
(Elmt
)) = N_Aggregate
then
3507 if Present
(Next_Index
(Ix
))
3510 (Expression
(Elmt
), Next_Index
(Ix
), Next_Index
(Ixb
))
3516 Component_Loop
: while Present
(Elmt
) loop
3517 Choice
:= First
(Choices
(Elmt
));
3518 Choice_Loop
: while Present
(Choice
) loop
3520 -- If we have an others choice, fill in the missing elements
3521 -- subject to the limit established by Max_Others_Replicate.
3523 if Nkind
(Choice
) = N_Others_Choice
then
3526 for J
in Vals
'Range loop
3527 if No
(Vals
(J
)) then
3528 Vals
(J
) := New_Copy_Tree
(Expression
(Elmt
));
3529 Rep_Count
:= Rep_Count
+ 1;
3531 -- Check for maximum others replication. Note that
3532 -- we skip this test if either of the restrictions
3533 -- No_Elaboration_Code or No_Implicit_Loops is
3534 -- active, if this is a preelaborable unit or
3535 -- a predefined unit, or if the unit must be
3536 -- placed in data memory. This also ensures that
3537 -- predefined units get the same level of constant
3538 -- folding in Ada 95 and Ada 2005, where their
3539 -- categorization has changed.
3542 P
: constant Entity_Id
:=
3543 Cunit_Entity
(Current_Sem_Unit
);
3546 -- Check if duplication OK and if so continue
3549 if Restriction_Active
(No_Elaboration_Code
)
3550 or else Restriction_Active
(No_Implicit_Loops
)
3552 (Ekind
(Current_Scope
) = E_Package
3554 Static_Elaboration_Desired
3556 or else Is_Preelaborated
(P
)
3557 or else (Ekind
(P
) = E_Package_Body
3559 Is_Preelaborated
(Spec_Entity
(P
)))
3561 Is_Predefined_File_Name
3562 (Unit_File_Name
(Get_Source_Unit
(P
)))
3566 -- If duplication not OK, then we return False
3567 -- if the replication count is too high
3569 elsif Rep_Count
> Max_Others_Replicate
then
3572 -- Continue on if duplication not OK, but the
3573 -- replication count is not excessive.
3582 exit Component_Loop
;
3584 -- Case of a subtype mark, identifier or expanded name
3586 elsif Is_Entity_Name
(Choice
)
3587 and then Is_Type
(Entity
(Choice
))
3589 Lo
:= Type_Low_Bound
(Etype
(Choice
));
3590 Hi
:= Type_High_Bound
(Etype
(Choice
));
3592 -- Case of subtype indication
3594 elsif Nkind
(Choice
) = N_Subtype_Indication
then
3595 Lo
:= Low_Bound
(Range_Expression
(Constraint
(Choice
)));
3596 Hi
:= High_Bound
(Range_Expression
(Constraint
(Choice
)));
3600 elsif Nkind
(Choice
) = N_Range
then
3601 Lo
:= Low_Bound
(Choice
);
3602 Hi
:= High_Bound
(Choice
);
3604 -- Normal subexpression case
3606 else pragma Assert
(Nkind
(Choice
) in N_Subexpr
);
3607 if not Compile_Time_Known_Value
(Choice
) then
3611 Choice_Index
:= UI_To_Int
(Expr_Value
(Choice
));
3612 if Choice_Index
in Vals
'Range then
3613 Vals
(Choice_Index
) :=
3614 New_Copy_Tree
(Expression
(Elmt
));
3618 -- Choice is statically out-of-range, will be
3619 -- rewritten to raise Constraint_Error.
3626 -- Range cases merge with Lo,Hi set
3628 if not Compile_Time_Known_Value
(Lo
)
3630 not Compile_Time_Known_Value
(Hi
)
3634 for J
in UI_To_Int
(Expr_Value
(Lo
)) ..
3635 UI_To_Int
(Expr_Value
(Hi
))
3637 Vals
(J
) := New_Copy_Tree
(Expression
(Elmt
));
3643 end loop Choice_Loop
;
3646 end loop Component_Loop
;
3648 -- If we get here the conversion is possible
3651 for J
in Vals
'Range loop
3652 Append
(Vals
(J
), Vlist
);
3655 Rewrite
(N
, Make_Aggregate
(Loc
, Expressions
=> Vlist
));
3656 Set_Aggregate_Bounds
(N
, Aggregate_Bounds
(Original_Node
(N
)));
3665 function Is_Flat
(N
: Node_Id
; Dims
: Int
) return Boolean is
3672 elsif Nkind
(N
) = N_Aggregate
then
3673 if Present
(Component_Associations
(N
)) then
3677 Elmt
:= First
(Expressions
(N
));
3678 while Present
(Elmt
) loop
3679 if not Is_Flat
(Elmt
, Dims
- 1) then
3693 -- Start of processing for Convert_To_Positional
3696 -- Ada 2005 (AI-287): Do not convert in case of default initialized
3697 -- components because in this case will need to call the corresponding
3700 if Has_Default_Init_Comps
(N
) then
3704 if Is_Flat
(N
, Number_Dimensions
(Typ
)) then
3708 if Is_Bit_Packed_Array
(Typ
)
3709 and then not Handle_Bit_Packed
3714 -- Do not convert to positional if controlled components are involved
3715 -- since these require special processing
3717 if Has_Controlled_Component
(Typ
) then
3721 Check_Static_Components
;
3723 -- If the size is known, or all the components are static, try to
3724 -- build a fully positional aggregate.
3726 -- The size of the type may not be known for an aggregate with
3727 -- discriminated array components, but if the components are static
3728 -- it is still possible to verify statically that the length is
3729 -- compatible with the upper bound of the type, and therefore it is
3730 -- worth flattening such aggregates as well.
3732 -- For now the back-end expands these aggregates into individual
3733 -- assignments to the target anyway, but it is conceivable that
3734 -- it will eventually be able to treat such aggregates statically???
3736 if Aggr_Size_OK
(N
, Typ
)
3737 and then Flatten
(N
, First_Index
(Typ
), First_Index
(Base_Type
(Typ
)))
3739 if Static_Components
then
3740 Set_Compile_Time_Known_Aggregate
(N
);
3741 Set_Expansion_Delayed
(N
, False);
3744 Analyze_And_Resolve
(N
, Typ
);
3747 -- Is Static_Eaboration_Desired has been specified, diagnose aggregates
3748 -- that will still require initialization code.
3750 if (Ekind
(Current_Scope
) = E_Package
3751 and then Static_Elaboration_Desired
(Current_Scope
))
3752 and then Nkind
(Parent
(N
)) = N_Object_Declaration
3758 if Nkind
(N
) = N_Aggregate
and then Present
(Expressions
(N
)) then
3759 Expr
:= First
(Expressions
(N
));
3760 while Present
(Expr
) loop
3761 if Nkind_In
(Expr
, N_Integer_Literal
, N_Real_Literal
)
3763 (Is_Entity_Name
(Expr
)
3764 and then Ekind
(Entity
(Expr
)) = E_Enumeration_Literal
)
3770 ("non-static object requires elaboration code?", N
);
3777 if Present
(Component_Associations
(N
)) then
3778 Error_Msg_N
("object requires elaboration code?", N
);
3783 end Convert_To_Positional
;
3785 ----------------------------
3786 -- Expand_Array_Aggregate --
3787 ----------------------------
3789 -- Array aggregate expansion proceeds as follows:
3791 -- 1. If requested we generate code to perform all the array aggregate
3792 -- bound checks, specifically
3794 -- (a) Check that the index range defined by aggregate bounds is
3795 -- compatible with corresponding index subtype.
3797 -- (b) If an others choice is present check that no aggregate
3798 -- index is outside the bounds of the index constraint.
3800 -- (c) For multidimensional arrays make sure that all subaggregates
3801 -- corresponding to the same dimension have the same bounds.
3803 -- 2. Check for packed array aggregate which can be converted to a
3804 -- constant so that the aggregate disappeares completely.
3806 -- 3. Check case of nested aggregate. Generally nested aggregates are
3807 -- handled during the processing of the parent aggregate.
3809 -- 4. Check if the aggregate can be statically processed. If this is the
3810 -- case pass it as is to Gigi. Note that a necessary condition for
3811 -- static processing is that the aggregate be fully positional.
3813 -- 5. If in place aggregate expansion is possible (i.e. no need to create
3814 -- a temporary) then mark the aggregate as such and return. Otherwise
3815 -- create a new temporary and generate the appropriate initialization
3818 procedure Expand_Array_Aggregate
(N
: Node_Id
) is
3819 Loc
: constant Source_Ptr
:= Sloc
(N
);
3821 Typ
: constant Entity_Id
:= Etype
(N
);
3822 Ctyp
: constant Entity_Id
:= Component_Type
(Typ
);
3823 -- Typ is the correct constrained array subtype of the aggregate
3824 -- Ctyp is the corresponding component type.
3826 Aggr_Dimension
: constant Pos
:= Number_Dimensions
(Typ
);
3827 -- Number of aggregate index dimensions
3829 Aggr_Low
: array (1 .. Aggr_Dimension
) of Node_Id
;
3830 Aggr_High
: array (1 .. Aggr_Dimension
) of Node_Id
;
3831 -- Low and High bounds of the constraint for each aggregate index
3833 Aggr_Index_Typ
: array (1 .. Aggr_Dimension
) of Entity_Id
;
3834 -- The type of each index
3836 Maybe_In_Place_OK
: Boolean;
3837 -- If the type is neither controlled nor packed and the aggregate
3838 -- is the expression in an assignment, assignment in place may be
3839 -- possible, provided other conditions are met on the LHS.
3841 Others_Present
: array (1 .. Aggr_Dimension
) of Boolean :=
3843 -- If Others_Present (J) is True, then there is an others choice
3844 -- in one of the sub-aggregates of N at dimension J.
3846 procedure Build_Constrained_Type
(Positional
: Boolean);
3847 -- If the subtype is not static or unconstrained, build a constrained
3848 -- type using the computable sizes of the aggregate and its sub-
3851 procedure Check_Bounds
(Aggr_Bounds
: Node_Id
; Index_Bounds
: Node_Id
);
3852 -- Checks that the bounds of Aggr_Bounds are within the bounds defined
3855 procedure Check_Same_Aggr_Bounds
(Sub_Aggr
: Node_Id
; Dim
: Pos
);
3856 -- Checks that in a multi-dimensional array aggregate all subaggregates
3857 -- corresponding to the same dimension have the same bounds.
3858 -- Sub_Aggr is an array sub-aggregate. Dim is the dimension
3859 -- corresponding to the sub-aggregate.
3861 procedure Compute_Others_Present
(Sub_Aggr
: Node_Id
; Dim
: Pos
);
3862 -- Computes the values of array Others_Present. Sub_Aggr is the
3863 -- array sub-aggregate we start the computation from. Dim is the
3864 -- dimension corresponding to the sub-aggregate.
3866 function In_Place_Assign_OK
return Boolean;
3867 -- Simple predicate to determine whether an aggregate assignment can
3868 -- be done in place, because none of the new values can depend on the
3869 -- components of the target of the assignment.
3871 procedure Others_Check
(Sub_Aggr
: Node_Id
; Dim
: Pos
);
3872 -- Checks that if an others choice is present in any sub-aggregate no
3873 -- aggregate index is outside the bounds of the index constraint.
3874 -- Sub_Aggr is an array sub-aggregate. Dim is the dimension
3875 -- corresponding to the sub-aggregate.
3877 function Safe_Left_Hand_Side
(N
: Node_Id
) return Boolean;
3878 -- In addition to Maybe_In_Place_OK, in order for an aggregate to be
3879 -- built directly into the target of the assignment it must be free
3882 ----------------------------
3883 -- Build_Constrained_Type --
3884 ----------------------------
3886 procedure Build_Constrained_Type
(Positional
: Boolean) is
3887 Loc
: constant Source_Ptr
:= Sloc
(N
);
3888 Agg_Type
: constant Entity_Id
:= Make_Temporary
(Loc
, 'A');
3891 Typ
: constant Entity_Id
:= Etype
(N
);
3892 Indexes
: constant List_Id
:= New_List
;
3897 -- If the aggregate is purely positional, all its subaggregates
3898 -- have the same size. We collect the dimensions from the first
3899 -- subaggregate at each level.
3904 for D
in 1 .. Number_Dimensions
(Typ
) loop
3905 Sub_Agg
:= First
(Expressions
(Sub_Agg
));
3909 while Present
(Comp
) loop
3916 Low_Bound
=> Make_Integer_Literal
(Loc
, 1),
3917 High_Bound
=> Make_Integer_Literal
(Loc
, Num
)));
3921 -- We know the aggregate type is unconstrained and the aggregate
3922 -- is not processable by the back end, therefore not necessarily
3923 -- positional. Retrieve each dimension bounds (computed earlier).
3925 for D
in 1 .. Number_Dimensions
(Typ
) loop
3928 Low_Bound
=> Aggr_Low
(D
),
3929 High_Bound
=> Aggr_High
(D
)),
3935 Make_Full_Type_Declaration
(Loc
,
3936 Defining_Identifier
=> Agg_Type
,
3938 Make_Constrained_Array_Definition
(Loc
,
3939 Discrete_Subtype_Definitions
=> Indexes
,
3940 Component_Definition
=>
3941 Make_Component_Definition
(Loc
,
3942 Aliased_Present
=> False,
3943 Subtype_Indication
=>
3944 New_Occurrence_Of
(Component_Type
(Typ
), Loc
))));
3946 Insert_Action
(N
, Decl
);
3948 Set_Etype
(N
, Agg_Type
);
3949 Set_Is_Itype
(Agg_Type
);
3950 Freeze_Itype
(Agg_Type
, N
);
3951 end Build_Constrained_Type
;
3957 procedure Check_Bounds
(Aggr_Bounds
: Node_Id
; Index_Bounds
: Node_Id
) is
3964 Cond
: Node_Id
:= Empty
;
3967 Get_Index_Bounds
(Aggr_Bounds
, Aggr_Lo
, Aggr_Hi
);
3968 Get_Index_Bounds
(Index_Bounds
, Ind_Lo
, Ind_Hi
);
3970 -- Generate the following test:
3972 -- [constraint_error when
3973 -- Aggr_Lo <= Aggr_Hi and then
3974 -- (Aggr_Lo < Ind_Lo or else Aggr_Hi > Ind_Hi)]
3976 -- As an optimization try to see if some tests are trivially vacuous
3977 -- because we are comparing an expression against itself.
3979 if Aggr_Lo
= Ind_Lo
and then Aggr_Hi
= Ind_Hi
then
3982 elsif Aggr_Hi
= Ind_Hi
then
3985 Left_Opnd
=> Duplicate_Subexpr_Move_Checks
(Aggr_Lo
),
3986 Right_Opnd
=> Duplicate_Subexpr_Move_Checks
(Ind_Lo
));
3988 elsif Aggr_Lo
= Ind_Lo
then
3991 Left_Opnd
=> Duplicate_Subexpr_Move_Checks
(Aggr_Hi
),
3992 Right_Opnd
=> Duplicate_Subexpr_Move_Checks
(Ind_Hi
));
3999 Left_Opnd
=> Duplicate_Subexpr_Move_Checks
(Aggr_Lo
),
4000 Right_Opnd
=> Duplicate_Subexpr_Move_Checks
(Ind_Lo
)),
4004 Left_Opnd
=> Duplicate_Subexpr
(Aggr_Hi
),
4005 Right_Opnd
=> Duplicate_Subexpr
(Ind_Hi
)));
4008 if Present
(Cond
) then
4013 Left_Opnd
=> Duplicate_Subexpr_Move_Checks
(Aggr_Lo
),
4014 Right_Opnd
=> Duplicate_Subexpr_Move_Checks
(Aggr_Hi
)),
4016 Right_Opnd
=> Cond
);
4018 Set_Analyzed
(Left_Opnd
(Left_Opnd
(Cond
)), False);
4019 Set_Analyzed
(Right_Opnd
(Left_Opnd
(Cond
)), False);
4021 Make_Raise_Constraint_Error
(Loc
,
4023 Reason
=> CE_Length_Check_Failed
));
4027 ----------------------------
4028 -- Check_Same_Aggr_Bounds --
4029 ----------------------------
4031 procedure Check_Same_Aggr_Bounds
(Sub_Aggr
: Node_Id
; Dim
: Pos
) is
4032 Sub_Lo
: constant Node_Id
:= Low_Bound
(Aggregate_Bounds
(Sub_Aggr
));
4033 Sub_Hi
: constant Node_Id
:= High_Bound
(Aggregate_Bounds
(Sub_Aggr
));
4034 -- The bounds of this specific sub-aggregate
4036 Aggr_Lo
: constant Node_Id
:= Aggr_Low
(Dim
);
4037 Aggr_Hi
: constant Node_Id
:= Aggr_High
(Dim
);
4038 -- The bounds of the aggregate for this dimension
4040 Ind_Typ
: constant Entity_Id
:= Aggr_Index_Typ
(Dim
);
4041 -- The index type for this dimension.xxx
4043 Cond
: Node_Id
:= Empty
;
4048 -- If index checks are on generate the test
4050 -- [constraint_error when
4051 -- Aggr_Lo /= Sub_Lo or else Aggr_Hi /= Sub_Hi]
4053 -- As an optimization try to see if some tests are trivially vacuos
4054 -- because we are comparing an expression against itself. Also for
4055 -- the first dimension the test is trivially vacuous because there
4056 -- is just one aggregate for dimension 1.
4058 if Index_Checks_Suppressed
(Ind_Typ
) then
4062 or else (Aggr_Lo
= Sub_Lo
and then Aggr_Hi
= Sub_Hi
)
4066 elsif Aggr_Hi
= Sub_Hi
then
4069 Left_Opnd
=> Duplicate_Subexpr_Move_Checks
(Aggr_Lo
),
4070 Right_Opnd
=> Duplicate_Subexpr_Move_Checks
(Sub_Lo
));
4072 elsif Aggr_Lo
= Sub_Lo
then
4075 Left_Opnd
=> Duplicate_Subexpr_Move_Checks
(Aggr_Hi
),
4076 Right_Opnd
=> Duplicate_Subexpr_Move_Checks
(Sub_Hi
));
4083 Left_Opnd
=> Duplicate_Subexpr_Move_Checks
(Aggr_Lo
),
4084 Right_Opnd
=> Duplicate_Subexpr_Move_Checks
(Sub_Lo
)),
4088 Left_Opnd
=> Duplicate_Subexpr
(Aggr_Hi
),
4089 Right_Opnd
=> Duplicate_Subexpr
(Sub_Hi
)));
4092 if Present
(Cond
) then
4094 Make_Raise_Constraint_Error
(Loc
,
4096 Reason
=> CE_Length_Check_Failed
));
4099 -- Now look inside the sub-aggregate to see if there is more work
4101 if Dim
< Aggr_Dimension
then
4103 -- Process positional components
4105 if Present
(Expressions
(Sub_Aggr
)) then
4106 Expr
:= First
(Expressions
(Sub_Aggr
));
4107 while Present
(Expr
) loop
4108 Check_Same_Aggr_Bounds
(Expr
, Dim
+ 1);
4113 -- Process component associations
4115 if Present
(Component_Associations
(Sub_Aggr
)) then
4116 Assoc
:= First
(Component_Associations
(Sub_Aggr
));
4117 while Present
(Assoc
) loop
4118 Expr
:= Expression
(Assoc
);
4119 Check_Same_Aggr_Bounds
(Expr
, Dim
+ 1);
4124 end Check_Same_Aggr_Bounds
;
4126 ----------------------------
4127 -- Compute_Others_Present --
4128 ----------------------------
4130 procedure Compute_Others_Present
(Sub_Aggr
: Node_Id
; Dim
: Pos
) is
4135 if Present
(Component_Associations
(Sub_Aggr
)) then
4136 Assoc
:= Last
(Component_Associations
(Sub_Aggr
));
4138 if Nkind
(First
(Choices
(Assoc
))) = N_Others_Choice
then
4139 Others_Present
(Dim
) := True;
4143 -- Now look inside the sub-aggregate to see if there is more work
4145 if Dim
< Aggr_Dimension
then
4147 -- Process positional components
4149 if Present
(Expressions
(Sub_Aggr
)) then
4150 Expr
:= First
(Expressions
(Sub_Aggr
));
4151 while Present
(Expr
) loop
4152 Compute_Others_Present
(Expr
, Dim
+ 1);
4157 -- Process component associations
4159 if Present
(Component_Associations
(Sub_Aggr
)) then
4160 Assoc
:= First
(Component_Associations
(Sub_Aggr
));
4161 while Present
(Assoc
) loop
4162 Expr
:= Expression
(Assoc
);
4163 Compute_Others_Present
(Expr
, Dim
+ 1);
4168 end Compute_Others_Present
;
4170 ------------------------
4171 -- In_Place_Assign_OK --
4172 ------------------------
4174 function In_Place_Assign_OK
return Boolean is
4182 function Safe_Aggregate
(Aggr
: Node_Id
) return Boolean;
4183 -- Check recursively that each component of a (sub)aggregate does
4184 -- not depend on the variable being assigned to.
4186 function Safe_Component
(Expr
: Node_Id
) return Boolean;
4187 -- Verify that an expression cannot depend on the variable being
4188 -- assigned to. Room for improvement here (but less than before).
4190 --------------------
4191 -- Safe_Aggregate --
4192 --------------------
4194 function Safe_Aggregate
(Aggr
: Node_Id
) return Boolean is
4198 if Present
(Expressions
(Aggr
)) then
4199 Expr
:= First
(Expressions
(Aggr
));
4200 while Present
(Expr
) loop
4201 if Nkind
(Expr
) = N_Aggregate
then
4202 if not Safe_Aggregate
(Expr
) then
4206 elsif not Safe_Component
(Expr
) then
4214 if Present
(Component_Associations
(Aggr
)) then
4215 Expr
:= First
(Component_Associations
(Aggr
));
4216 while Present
(Expr
) loop
4217 if Nkind
(Expression
(Expr
)) = N_Aggregate
then
4218 if not Safe_Aggregate
(Expression
(Expr
)) then
4222 -- If association has a box, no way to determine yet
4223 -- whether default can be assigned in place.
4225 elsif Box_Present
(Expr
) then
4228 elsif not Safe_Component
(Expression
(Expr
)) then
4239 --------------------
4240 -- Safe_Component --
4241 --------------------
4243 function Safe_Component
(Expr
: Node_Id
) return Boolean is
4244 Comp
: Node_Id
:= Expr
;
4246 function Check_Component
(Comp
: Node_Id
) return Boolean;
4247 -- Do the recursive traversal, after copy
4249 ---------------------
4250 -- Check_Component --
4251 ---------------------
4253 function Check_Component
(Comp
: Node_Id
) return Boolean is
4255 if Is_Overloaded
(Comp
) then
4259 return Compile_Time_Known_Value
(Comp
)
4261 or else (Is_Entity_Name
(Comp
)
4262 and then Present
(Entity
(Comp
))
4263 and then No
(Renamed_Object
(Entity
(Comp
))))
4265 or else (Nkind
(Comp
) = N_Attribute_Reference
4266 and then Check_Component
(Prefix
(Comp
)))
4268 or else (Nkind
(Comp
) in N_Binary_Op
4269 and then Check_Component
(Left_Opnd
(Comp
))
4270 and then Check_Component
(Right_Opnd
(Comp
)))
4272 or else (Nkind
(Comp
) in N_Unary_Op
4273 and then Check_Component
(Right_Opnd
(Comp
)))
4275 or else (Nkind
(Comp
) = N_Selected_Component
4276 and then Check_Component
(Prefix
(Comp
)))
4278 or else (Nkind
(Comp
) = N_Unchecked_Type_Conversion
4279 and then Check_Component
(Expression
(Comp
)));
4280 end Check_Component
;
4282 -- Start of processing for Safe_Component
4285 -- If the component appears in an association that may
4286 -- correspond to more than one element, it is not analyzed
4287 -- before the expansion into assignments, to avoid side effects.
4288 -- We analyze, but do not resolve the copy, to obtain sufficient
4289 -- entity information for the checks that follow. If component is
4290 -- overloaded we assume an unsafe function call.
4292 if not Analyzed
(Comp
) then
4293 if Is_Overloaded
(Expr
) then
4296 elsif Nkind
(Expr
) = N_Aggregate
4297 and then not Is_Others_Aggregate
(Expr
)
4301 elsif Nkind
(Expr
) = N_Allocator
then
4303 -- For now, too complex to analyze
4308 Comp
:= New_Copy_Tree
(Expr
);
4309 Set_Parent
(Comp
, Parent
(Expr
));
4313 if Nkind
(Comp
) = N_Aggregate
then
4314 return Safe_Aggregate
(Comp
);
4316 return Check_Component
(Comp
);
4320 -- Start of processing for In_Place_Assign_OK
4323 if Present
(Component_Associations
(N
)) then
4325 -- On assignment, sliding can take place, so we cannot do the
4326 -- assignment in place unless the bounds of the aggregate are
4327 -- statically equal to those of the target.
4329 -- If the aggregate is given by an others choice, the bounds
4330 -- are derived from the left-hand side, and the assignment is
4331 -- safe if the expression is.
4333 if Is_Others_Aggregate
(N
) then
4336 (Expression
(First
(Component_Associations
(N
))));
4339 Aggr_In
:= First_Index
(Etype
(N
));
4341 if Nkind
(Parent
(N
)) = N_Assignment_Statement
then
4342 Obj_In
:= First_Index
(Etype
(Name
(Parent
(N
))));
4345 -- Context is an allocator. Check bounds of aggregate
4346 -- against given type in qualified expression.
4348 pragma Assert
(Nkind
(Parent
(Parent
(N
))) = N_Allocator
);
4350 First_Index
(Etype
(Entity
(Subtype_Mark
(Parent
(N
)))));
4353 while Present
(Aggr_In
) loop
4354 Get_Index_Bounds
(Aggr_In
, Aggr_Lo
, Aggr_Hi
);
4355 Get_Index_Bounds
(Obj_In
, Obj_Lo
, Obj_Hi
);
4357 if not Compile_Time_Known_Value
(Aggr_Lo
)
4358 or else not Compile_Time_Known_Value
(Aggr_Hi
)
4359 or else not Compile_Time_Known_Value
(Obj_Lo
)
4360 or else not Compile_Time_Known_Value
(Obj_Hi
)
4361 or else Expr_Value
(Aggr_Lo
) /= Expr_Value
(Obj_Lo
)
4362 or else Expr_Value
(Aggr_Hi
) /= Expr_Value
(Obj_Hi
)
4367 Next_Index
(Aggr_In
);
4368 Next_Index
(Obj_In
);
4372 -- Now check the component values themselves
4374 return Safe_Aggregate
(N
);
4375 end In_Place_Assign_OK
;
4381 procedure Others_Check
(Sub_Aggr
: Node_Id
; Dim
: Pos
) is
4382 Aggr_Lo
: constant Node_Id
:= Aggr_Low
(Dim
);
4383 Aggr_Hi
: constant Node_Id
:= Aggr_High
(Dim
);
4384 -- The bounds of the aggregate for this dimension
4386 Ind_Typ
: constant Entity_Id
:= Aggr_Index_Typ
(Dim
);
4387 -- The index type for this dimension
4389 Need_To_Check
: Boolean := False;
4391 Choices_Lo
: Node_Id
:= Empty
;
4392 Choices_Hi
: Node_Id
:= Empty
;
4393 -- The lowest and highest discrete choices for a named sub-aggregate
4395 Nb_Choices
: Int
:= -1;
4396 -- The number of discrete non-others choices in this sub-aggregate
4398 Nb_Elements
: Uint
:= Uint_0
;
4399 -- The number of elements in a positional aggregate
4401 Cond
: Node_Id
:= Empty
;
4408 -- Check if we have an others choice. If we do make sure that this
4409 -- sub-aggregate contains at least one element in addition to the
4412 if Range_Checks_Suppressed
(Ind_Typ
) then
4413 Need_To_Check
:= False;
4415 elsif Present
(Expressions
(Sub_Aggr
))
4416 and then Present
(Component_Associations
(Sub_Aggr
))
4418 Need_To_Check
:= True;
4420 elsif Present
(Component_Associations
(Sub_Aggr
)) then
4421 Assoc
:= Last
(Component_Associations
(Sub_Aggr
));
4423 if Nkind
(First
(Choices
(Assoc
))) /= N_Others_Choice
then
4424 Need_To_Check
:= False;
4427 -- Count the number of discrete choices. Start with -1 because
4428 -- the others choice does not count.
4431 Assoc
:= First
(Component_Associations
(Sub_Aggr
));
4432 while Present
(Assoc
) loop
4433 Choice
:= First
(Choices
(Assoc
));
4434 while Present
(Choice
) loop
4435 Nb_Choices
:= Nb_Choices
+ 1;
4442 -- If there is only an others choice nothing to do
4444 Need_To_Check
:= (Nb_Choices
> 0);
4448 Need_To_Check
:= False;
4451 -- If we are dealing with a positional sub-aggregate with an others
4452 -- choice then compute the number or positional elements.
4454 if Need_To_Check
and then Present
(Expressions
(Sub_Aggr
)) then
4455 Expr
:= First
(Expressions
(Sub_Aggr
));
4456 Nb_Elements
:= Uint_0
;
4457 while Present
(Expr
) loop
4458 Nb_Elements
:= Nb_Elements
+ 1;
4462 -- If the aggregate contains discrete choices and an others choice
4463 -- compute the smallest and largest discrete choice values.
4465 elsif Need_To_Check
then
4466 Compute_Choices_Lo_And_Choices_Hi
: declare
4468 Table
: Case_Table_Type
(1 .. Nb_Choices
);
4469 -- Used to sort all the different choice values
4476 Assoc
:= First
(Component_Associations
(Sub_Aggr
));
4477 while Present
(Assoc
) loop
4478 Choice
:= First
(Choices
(Assoc
));
4479 while Present
(Choice
) loop
4480 if Nkind
(Choice
) = N_Others_Choice
then
4484 Get_Index_Bounds
(Choice
, Low
, High
);
4485 Table
(J
).Choice_Lo
:= Low
;
4486 Table
(J
).Choice_Hi
:= High
;
4495 -- Sort the discrete choices
4497 Sort_Case_Table
(Table
);
4499 Choices_Lo
:= Table
(1).Choice_Lo
;
4500 Choices_Hi
:= Table
(Nb_Choices
).Choice_Hi
;
4501 end Compute_Choices_Lo_And_Choices_Hi
;
4504 -- If no others choice in this sub-aggregate, or the aggregate
4505 -- comprises only an others choice, nothing to do.
4507 if not Need_To_Check
then
4510 -- If we are dealing with an aggregate containing an others choice
4511 -- and positional components, we generate the following test:
4513 -- if Ind_Typ'Pos (Aggr_Lo) + (Nb_Elements - 1) >
4514 -- Ind_Typ'Pos (Aggr_Hi)
4516 -- raise Constraint_Error;
4519 elsif Nb_Elements
> Uint_0
then
4525 Make_Attribute_Reference
(Loc
,
4526 Prefix
=> New_Reference_To
(Ind_Typ
, Loc
),
4527 Attribute_Name
=> Name_Pos
,
4530 (Duplicate_Subexpr_Move_Checks
(Aggr_Lo
))),
4531 Right_Opnd
=> Make_Integer_Literal
(Loc
, Nb_Elements
- 1)),
4534 Make_Attribute_Reference
(Loc
,
4535 Prefix
=> New_Reference_To
(Ind_Typ
, Loc
),
4536 Attribute_Name
=> Name_Pos
,
4537 Expressions
=> New_List
(
4538 Duplicate_Subexpr_Move_Checks
(Aggr_Hi
))));
4540 -- If we are dealing with an aggregate containing an others choice
4541 -- and discrete choices we generate the following test:
4543 -- [constraint_error when
4544 -- Choices_Lo < Aggr_Lo or else Choices_Hi > Aggr_Hi];
4552 Duplicate_Subexpr_Move_Checks
(Choices_Lo
),
4554 Duplicate_Subexpr_Move_Checks
(Aggr_Lo
)),
4559 Duplicate_Subexpr
(Choices_Hi
),
4561 Duplicate_Subexpr
(Aggr_Hi
)));
4564 if Present
(Cond
) then
4566 Make_Raise_Constraint_Error
(Loc
,
4568 Reason
=> CE_Length_Check_Failed
));
4569 -- Questionable reason code, shouldn't that be a
4570 -- CE_Range_Check_Failed ???
4573 -- Now look inside the sub-aggregate to see if there is more work
4575 if Dim
< Aggr_Dimension
then
4577 -- Process positional components
4579 if Present
(Expressions
(Sub_Aggr
)) then
4580 Expr
:= First
(Expressions
(Sub_Aggr
));
4581 while Present
(Expr
) loop
4582 Others_Check
(Expr
, Dim
+ 1);
4587 -- Process component associations
4589 if Present
(Component_Associations
(Sub_Aggr
)) then
4590 Assoc
:= First
(Component_Associations
(Sub_Aggr
));
4591 while Present
(Assoc
) loop
4592 Expr
:= Expression
(Assoc
);
4593 Others_Check
(Expr
, Dim
+ 1);
4600 -------------------------
4601 -- Safe_Left_Hand_Side --
4602 -------------------------
4604 function Safe_Left_Hand_Side
(N
: Node_Id
) return Boolean is
4605 function Is_Safe_Index
(Indx
: Node_Id
) return Boolean;
4606 -- If the left-hand side includes an indexed component, check that
4607 -- the indexes are free of side-effect.
4613 function Is_Safe_Index
(Indx
: Node_Id
) return Boolean is
4615 if Is_Entity_Name
(Indx
) then
4618 elsif Nkind
(Indx
) = N_Integer_Literal
then
4621 elsif Nkind
(Indx
) = N_Function_Call
4622 and then Is_Entity_Name
(Name
(Indx
))
4624 Has_Pragma_Pure_Function
(Entity
(Name
(Indx
)))
4628 elsif Nkind
(Indx
) = N_Type_Conversion
4629 and then Is_Safe_Index
(Expression
(Indx
))
4638 -- Start of processing for Safe_Left_Hand_Side
4641 if Is_Entity_Name
(N
) then
4644 elsif Nkind_In
(N
, N_Explicit_Dereference
, N_Selected_Component
)
4645 and then Safe_Left_Hand_Side
(Prefix
(N
))
4649 elsif Nkind
(N
) = N_Indexed_Component
4650 and then Safe_Left_Hand_Side
(Prefix
(N
))
4652 Is_Safe_Index
(First
(Expressions
(N
)))
4656 elsif Nkind
(N
) = N_Unchecked_Type_Conversion
then
4657 return Safe_Left_Hand_Side
(Expression
(N
));
4662 end Safe_Left_Hand_Side
;
4667 -- Holds the temporary aggregate value
4670 -- Holds the declaration of Tmp
4672 Aggr_Code
: List_Id
;
4673 Parent_Node
: Node_Id
;
4674 Parent_Kind
: Node_Kind
;
4676 -- Start of processing for Expand_Array_Aggregate
4679 -- Do not touch the special aggregates of attributes used for Asm calls
4681 if Is_RTE
(Ctyp
, RE_Asm_Input_Operand
)
4682 or else Is_RTE
(Ctyp
, RE_Asm_Output_Operand
)
4686 -- Do not expand an aggregate for an array type which contains tasks if
4687 -- the aggregate is associated with an unexpanded return statement of a
4688 -- build-in-place function. The aggregate is expanded when the related
4689 -- return statement (rewritten into an extended return) is processed.
4690 -- This delay ensures that any temporaries and initialization code
4691 -- generated for the aggregate appear in the proper return block and
4692 -- use the correct _chain and _master.
4694 elsif Has_Task
(Base_Type
(Etype
(N
)))
4695 and then Nkind
(Parent
(N
)) = N_Simple_Return_Statement
4696 and then Is_Build_In_Place_Function
4697 (Return_Applies_To
(Return_Statement_Entity
(Parent
(N
))))
4702 -- If the semantic analyzer has determined that aggregate N will raise
4703 -- Constraint_Error at run time, then the aggregate node has been
4704 -- replaced with an N_Raise_Constraint_Error node and we should
4707 pragma Assert
(not Raises_Constraint_Error
(N
));
4711 -- Check that the index range defined by aggregate bounds is
4712 -- compatible with corresponding index subtype.
4714 Index_Compatibility_Check
: declare
4715 Aggr_Index_Range
: Node_Id
:= First_Index
(Typ
);
4716 -- The current aggregate index range
4718 Index_Constraint
: Node_Id
:= First_Index
(Etype
(Typ
));
4719 -- The corresponding index constraint against which we have to
4720 -- check the above aggregate index range.
4723 Compute_Others_Present
(N
, 1);
4725 for J
in 1 .. Aggr_Dimension
loop
4726 -- There is no need to emit a check if an others choice is
4727 -- present for this array aggregate dimension since in this
4728 -- case one of N's sub-aggregates has taken its bounds from the
4729 -- context and these bounds must have been checked already. In
4730 -- addition all sub-aggregates corresponding to the same
4731 -- dimension must all have the same bounds (checked in (c) below).
4733 if not Range_Checks_Suppressed
(Etype
(Index_Constraint
))
4734 and then not Others_Present
(J
)
4736 -- We don't use Checks.Apply_Range_Check here because it emits
4737 -- a spurious check. Namely it checks that the range defined by
4738 -- the aggregate bounds is non empty. But we know this already
4741 Check_Bounds
(Aggr_Index_Range
, Index_Constraint
);
4744 -- Save the low and high bounds of the aggregate index as well as
4745 -- the index type for later use in checks (b) and (c) below.
4747 Aggr_Low
(J
) := Low_Bound
(Aggr_Index_Range
);
4748 Aggr_High
(J
) := High_Bound
(Aggr_Index_Range
);
4750 Aggr_Index_Typ
(J
) := Etype
(Index_Constraint
);
4752 Next_Index
(Aggr_Index_Range
);
4753 Next_Index
(Index_Constraint
);
4755 end Index_Compatibility_Check
;
4759 -- If an others choice is present check that no aggregate index is
4760 -- outside the bounds of the index constraint.
4762 Others_Check
(N
, 1);
4766 -- For multidimensional arrays make sure that all subaggregates
4767 -- corresponding to the same dimension have the same bounds.
4769 if Aggr_Dimension
> 1 then
4770 Check_Same_Aggr_Bounds
(N
, 1);
4775 -- Here we test for is packed array aggregate that we can handle at
4776 -- compile time. If so, return with transformation done. Note that we do
4777 -- this even if the aggregate is nested, because once we have done this
4778 -- processing, there is no more nested aggregate!
4780 if Packed_Array_Aggregate_Handled
(N
) then
4784 -- At this point we try to convert to positional form
4786 if Ekind
(Current_Scope
) = E_Package
4787 and then Static_Elaboration_Desired
(Current_Scope
)
4789 Convert_To_Positional
(N
, Max_Others_Replicate
=> 100);
4791 Convert_To_Positional
(N
);
4794 -- if the result is no longer an aggregate (e.g. it may be a string
4795 -- literal, or a temporary which has the needed value), then we are
4796 -- done, since there is no longer a nested aggregate.
4798 if Nkind
(N
) /= N_Aggregate
then
4801 -- We are also done if the result is an analyzed aggregate, indicating
4802 -- that Convert_To_Positional succeeded and reanalyzed the rewritten
4806 and then N
/= Original_Node
(N
)
4811 -- If all aggregate components are compile-time known and the aggregate
4812 -- has been flattened, nothing left to do. The same occurs if the
4813 -- aggregate is used to initialize the components of an statically
4814 -- allocated dispatch table.
4816 if Compile_Time_Known_Aggregate
(N
)
4817 or else Is_Static_Dispatch_Table_Aggregate
(N
)
4819 Set_Expansion_Delayed
(N
, False);
4823 -- Now see if back end processing is possible
4825 if Backend_Processing_Possible
(N
) then
4827 -- If the aggregate is static but the constraints are not, build
4828 -- a static subtype for the aggregate, so that Gigi can place it
4829 -- in static memory. Perform an unchecked_conversion to the non-
4830 -- static type imposed by the context.
4833 Itype
: constant Entity_Id
:= Etype
(N
);
4835 Needs_Type
: Boolean := False;
4838 Index
:= First_Index
(Itype
);
4839 while Present
(Index
) loop
4840 if not Is_Static_Subtype
(Etype
(Index
)) then
4849 Build_Constrained_Type
(Positional
=> True);
4850 Rewrite
(N
, Unchecked_Convert_To
(Itype
, N
));
4860 -- Delay expansion for nested aggregates: it will be taken care of
4861 -- when the parent aggregate is expanded.
4863 Parent_Node
:= Parent
(N
);
4864 Parent_Kind
:= Nkind
(Parent_Node
);
4866 if Parent_Kind
= N_Qualified_Expression
then
4867 Parent_Node
:= Parent
(Parent_Node
);
4868 Parent_Kind
:= Nkind
(Parent_Node
);
4871 if Parent_Kind
= N_Aggregate
4872 or else Parent_Kind
= N_Extension_Aggregate
4873 or else Parent_Kind
= N_Component_Association
4874 or else (Parent_Kind
= N_Object_Declaration
4875 and then Needs_Finalization
(Typ
))
4876 or else (Parent_Kind
= N_Assignment_Statement
4877 and then Inside_Init_Proc
)
4879 if Static_Array_Aggregate
(N
)
4880 or else Compile_Time_Known_Aggregate
(N
)
4882 Set_Expansion_Delayed
(N
, False);
4885 Set_Expansion_Delayed
(N
);
4892 -- Look if in place aggregate expansion is possible
4894 -- For object declarations we build the aggregate in place, unless
4895 -- the array is bit-packed or the component is controlled.
4897 -- For assignments we do the assignment in place if all the component
4898 -- associations have compile-time known values. For other cases we
4899 -- create a temporary. The analysis for safety of on-line assignment
4900 -- is delicate, i.e. we don't know how to do it fully yet ???
4902 -- For allocators we assign to the designated object in place if the
4903 -- aggregate meets the same conditions as other in-place assignments.
4904 -- In this case the aggregate may not come from source but was created
4905 -- for default initialization, e.g. with Initialize_Scalars.
4907 if Requires_Transient_Scope
(Typ
) then
4908 Establish_Transient_Scope
4909 (N
, Sec_Stack
=> Has_Controlled_Component
(Typ
));
4912 if Has_Default_Init_Comps
(N
) then
4913 Maybe_In_Place_OK
:= False;
4915 elsif Is_Bit_Packed_Array
(Typ
)
4916 or else Has_Controlled_Component
(Typ
)
4918 Maybe_In_Place_OK
:= False;
4921 Maybe_In_Place_OK
:=
4922 (Nkind
(Parent
(N
)) = N_Assignment_Statement
4923 and then Comes_From_Source
(N
)
4924 and then In_Place_Assign_OK
)
4927 (Nkind
(Parent
(Parent
(N
))) = N_Allocator
4928 and then In_Place_Assign_OK
);
4931 -- If this is an array of tasks, it will be expanded into build-in-place
4932 -- assignments. Build an activation chain for the tasks now.
4934 if Has_Task
(Etype
(N
)) then
4935 Build_Activation_Chain_Entity
(N
);
4938 -- Should document these individual tests ???
4940 if not Has_Default_Init_Comps
(N
)
4941 and then Comes_From_Source
(Parent
(N
))
4942 and then Nkind
(Parent
(N
)) = N_Object_Declaration
4944 Must_Slide
(Etype
(Defining_Identifier
(Parent
(N
))), Typ
)
4945 and then N
= Expression
(Parent
(N
))
4946 and then not Is_Bit_Packed_Array
(Typ
)
4947 and then not Has_Controlled_Component
(Typ
)
4949 -- If the aggregate is the expression in an object declaration, it
4950 -- cannot be expanded in place. Lookahead in the current declarative
4951 -- part to find an address clause for the object being declared. If
4952 -- one is present, we cannot build in place. Unclear comment???
4954 and then not Has_Following_Address_Clause
(Parent
(N
))
4956 Tmp
:= Defining_Identifier
(Parent
(N
));
4957 Set_No_Initialization
(Parent
(N
));
4958 Set_Expression
(Parent
(N
), Empty
);
4960 -- Set the type of the entity, for use in the analysis of the
4961 -- subsequent indexed assignments. If the nominal type is not
4962 -- constrained, build a subtype from the known bounds of the
4963 -- aggregate. If the declaration has a subtype mark, use it,
4964 -- otherwise use the itype of the aggregate.
4966 if not Is_Constrained
(Typ
) then
4967 Build_Constrained_Type
(Positional
=> False);
4968 elsif Is_Entity_Name
(Object_Definition
(Parent
(N
)))
4969 and then Is_Constrained
(Entity
(Object_Definition
(Parent
(N
))))
4971 Set_Etype
(Tmp
, Entity
(Object_Definition
(Parent
(N
))));
4973 Set_Size_Known_At_Compile_Time
(Typ
, False);
4974 Set_Etype
(Tmp
, Typ
);
4977 elsif Maybe_In_Place_OK
4978 and then Nkind
(Parent
(N
)) = N_Qualified_Expression
4979 and then Nkind
(Parent
(Parent
(N
))) = N_Allocator
4981 Set_Expansion_Delayed
(N
);
4984 -- In the remaining cases the aggregate is the RHS of an assignment
4986 elsif Maybe_In_Place_OK
4987 and then Safe_Left_Hand_Side
(Name
(Parent
(N
)))
4989 Tmp
:= Name
(Parent
(N
));
4991 if Etype
(Tmp
) /= Etype
(N
) then
4992 Apply_Length_Check
(N
, Etype
(Tmp
));
4994 if Nkind
(N
) = N_Raise_Constraint_Error
then
4996 -- Static error, nothing further to expand
5002 elsif Maybe_In_Place_OK
5003 and then Nkind
(Name
(Parent
(N
))) = N_Slice
5004 and then Safe_Slice_Assignment
(N
)
5006 -- Safe_Slice_Assignment rewrites assignment as a loop
5012 -- In place aggregate expansion is not possible
5015 Maybe_In_Place_OK
:= False;
5016 Tmp
:= Make_Temporary
(Loc
, 'A', N
);
5018 Make_Object_Declaration
5020 Defining_Identifier
=> Tmp
,
5021 Object_Definition
=> New_Occurrence_Of
(Typ
, Loc
));
5022 Set_No_Initialization
(Tmp_Decl
, True);
5024 -- If we are within a loop, the temporary will be pushed on the
5025 -- stack at each iteration. If the aggregate is the expression for an
5026 -- allocator, it will be immediately copied to the heap and can
5027 -- be reclaimed at once. We create a transient scope around the
5028 -- aggregate for this purpose.
5030 if Ekind
(Current_Scope
) = E_Loop
5031 and then Nkind
(Parent
(Parent
(N
))) = N_Allocator
5033 Establish_Transient_Scope
(N
, False);
5036 Insert_Action
(N
, Tmp_Decl
);
5039 -- Construct and insert the aggregate code. We can safely suppress index
5040 -- checks because this code is guaranteed not to raise CE on index
5041 -- checks. However we should *not* suppress all checks.
5047 if Nkind
(Tmp
) = N_Defining_Identifier
then
5048 Target
:= New_Reference_To
(Tmp
, Loc
);
5052 if Has_Default_Init_Comps
(N
) then
5054 -- Ada 2005 (AI-287): This case has not been analyzed???
5056 raise Program_Error
;
5059 -- Name in assignment is explicit dereference
5061 Target
:= New_Copy
(Tmp
);
5065 Build_Array_Aggr_Code
(N
,
5067 Index
=> First_Index
(Typ
),
5069 Scalar_Comp
=> Is_Scalar_Type
(Ctyp
));
5072 if Comes_From_Source
(Tmp
) then
5073 Insert_Actions_After
(Parent
(N
), Aggr_Code
);
5076 Insert_Actions
(N
, Aggr_Code
);
5079 -- If the aggregate has been assigned in place, remove the original
5082 if Nkind
(Parent
(N
)) = N_Assignment_Statement
5083 and then Maybe_In_Place_OK
5085 Rewrite
(Parent
(N
), Make_Null_Statement
(Loc
));
5087 elsif Nkind
(Parent
(N
)) /= N_Object_Declaration
5088 or else Tmp
/= Defining_Identifier
(Parent
(N
))
5090 Rewrite
(N
, New_Occurrence_Of
(Tmp
, Loc
));
5091 Analyze_And_Resolve
(N
, Typ
);
5093 end Expand_Array_Aggregate
;
5095 ------------------------
5096 -- Expand_N_Aggregate --
5097 ------------------------
5099 procedure Expand_N_Aggregate
(N
: Node_Id
) is
5101 if Is_Record_Type
(Etype
(N
)) then
5102 Expand_Record_Aggregate
(N
);
5104 Expand_Array_Aggregate
(N
);
5107 when RE_Not_Available
=>
5109 end Expand_N_Aggregate
;
5111 ----------------------------------
5112 -- Expand_N_Extension_Aggregate --
5113 ----------------------------------
5115 -- If the ancestor part is an expression, add a component association for
5116 -- the parent field. If the type of the ancestor part is not the direct
5117 -- parent of the expected type, build recursively the needed ancestors.
5118 -- If the ancestor part is a subtype_mark, replace aggregate with a decla-
5119 -- ration for a temporary of the expected type, followed by individual
5120 -- assignments to the given components.
5122 procedure Expand_N_Extension_Aggregate
(N
: Node_Id
) is
5123 Loc
: constant Source_Ptr
:= Sloc
(N
);
5124 A
: constant Node_Id
:= Ancestor_Part
(N
);
5125 Typ
: constant Entity_Id
:= Etype
(N
);
5128 -- If the ancestor is a subtype mark, an init proc must be called
5129 -- on the resulting object which thus has to be materialized in
5132 if Is_Entity_Name
(A
) and then Is_Type
(Entity
(A
)) then
5133 Convert_To_Assignments
(N
, Typ
);
5135 -- The extension aggregate is transformed into a record aggregate
5136 -- of the following form (c1 and c2 are inherited components)
5138 -- (Exp with c3 => a, c4 => b)
5139 -- ==> (c1 => Exp.c1, c2 => Exp.c2, c3 => a, c4 => b)
5144 if Tagged_Type_Expansion
then
5145 Expand_Record_Aggregate
(N
,
5148 (Node
(First_Elmt
(Access_Disp_Table
(Typ
))), Loc
),
5151 -- No tag is needed in the case of a VM
5154 Expand_Record_Aggregate
(N
, Parent_Expr
=> A
);
5159 when RE_Not_Available
=>
5161 end Expand_N_Extension_Aggregate
;
5163 -----------------------------
5164 -- Expand_Record_Aggregate --
5165 -----------------------------
5167 procedure Expand_Record_Aggregate
5169 Orig_Tag
: Node_Id
:= Empty
;
5170 Parent_Expr
: Node_Id
:= Empty
)
5172 Loc
: constant Source_Ptr
:= Sloc
(N
);
5173 Comps
: constant List_Id
:= Component_Associations
(N
);
5174 Typ
: constant Entity_Id
:= Etype
(N
);
5175 Base_Typ
: constant Entity_Id
:= Base_Type
(Typ
);
5177 Static_Components
: Boolean := True;
5178 -- Flag to indicate whether all components are compile-time known,
5179 -- and the aggregate can be constructed statically and handled by
5182 function Compile_Time_Known_Composite_Value
(N
: Node_Id
) return Boolean;
5183 -- Returns true if N is an expression of composite type which can be
5184 -- fully evaluated at compile time without raising constraint error.
5185 -- Such expressions can be passed as is to Gigi without any expansion.
5187 -- This returns true for N_Aggregate with Compile_Time_Known_Aggregate
5188 -- set and constants whose expression is such an aggregate, recursively.
5190 function Component_Not_OK_For_Backend
return Boolean;
5191 -- Check for presence of component which makes it impossible for the
5192 -- backend to process the aggregate, thus requiring the use of a series
5193 -- of assignment statements. Cases checked for are a nested aggregate
5194 -- needing Late_Expansion, the presence of a tagged component which may
5195 -- need tag adjustment, and a bit unaligned component reference.
5197 -- We also force expansion into assignments if a component is of a
5198 -- mutable type (including a private type with discriminants) because
5199 -- in that case the size of the component to be copied may be smaller
5200 -- than the side of the target, and there is no simple way for gigi
5201 -- to compute the size of the object to be copied.
5203 -- NOTE: This is part of the ongoing work to define precisely the
5204 -- interface between front-end and back-end handling of aggregates.
5205 -- In general it is desirable to pass aggregates as they are to gigi,
5206 -- in order to minimize elaboration code. This is one case where the
5207 -- semantics of Ada complicate the analysis and lead to anomalies in
5208 -- the gcc back-end if the aggregate is not expanded into assignments.
5210 function Has_Visible_Private_Ancestor
(Id
: E
) return Boolean;
5211 -- If any ancestor of the current type is private, the aggregate
5212 -- cannot be built in place. We canot rely on Has_Private_Ancestor,
5213 -- because it will not be set when type and its parent are in the
5214 -- same scope, and the parent component needs expansion.
5216 function Top_Level_Aggregate
(N
: Node_Id
) return Node_Id
;
5217 -- For nested aggregates return the ultimate enclosing aggregate; for
5218 -- non-nested aggregates return N.
5220 ----------------------------------------
5221 -- Compile_Time_Known_Composite_Value --
5222 ----------------------------------------
5224 function Compile_Time_Known_Composite_Value
5225 (N
: Node_Id
) return Boolean
5228 -- If we have an entity name, then see if it is the name of a
5229 -- constant and if so, test the corresponding constant value.
5231 if Is_Entity_Name
(N
) then
5233 E
: constant Entity_Id
:= Entity
(N
);
5236 if Ekind
(E
) /= E_Constant
then
5239 V
:= Constant_Value
(E
);
5241 and then Compile_Time_Known_Composite_Value
(V
);
5245 -- We have a value, see if it is compile time known
5248 if Nkind
(N
) = N_Aggregate
then
5249 return Compile_Time_Known_Aggregate
(N
);
5252 -- All other types of values are not known at compile time
5257 end Compile_Time_Known_Composite_Value
;
5259 ----------------------------------
5260 -- Component_Not_OK_For_Backend --
5261 ----------------------------------
5263 function Component_Not_OK_For_Backend
return Boolean is
5273 while Present
(C
) loop
5275 -- If the component has box initialization, expansion is needed
5276 -- and component is not ready for backend.
5278 if Box_Present
(C
) then
5282 if Nkind
(Expression
(C
)) = N_Qualified_Expression
then
5283 Expr_Q
:= Expression
(Expression
(C
));
5285 Expr_Q
:= Expression
(C
);
5288 -- Return true if the aggregate has any associations for tagged
5289 -- components that may require tag adjustment.
5291 -- These are cases where the source expression may have a tag that
5292 -- could differ from the component tag (e.g., can occur for type
5293 -- conversions and formal parameters). (Tag adjustment not needed
5294 -- if VM_Target because object tags are implicit in the machine.)
5296 if Is_Tagged_Type
(Etype
(Expr_Q
))
5297 and then (Nkind
(Expr_Q
) = N_Type_Conversion
5298 or else (Is_Entity_Name
(Expr_Q
)
5300 Ekind
(Entity
(Expr_Q
)) in Formal_Kind
))
5301 and then Tagged_Type_Expansion
5303 Static_Components
:= False;
5306 elsif Is_Delayed_Aggregate
(Expr_Q
) then
5307 Static_Components
:= False;
5310 elsif Possible_Bit_Aligned_Component
(Expr_Q
) then
5311 Static_Components
:= False;
5315 if Is_Elementary_Type
(Etype
(Expr_Q
)) then
5316 if not Compile_Time_Known_Value
(Expr_Q
) then
5317 Static_Components
:= False;
5320 elsif not Compile_Time_Known_Composite_Value
(Expr_Q
) then
5321 Static_Components
:= False;
5323 if Is_Private_Type
(Etype
(Expr_Q
))
5324 and then Has_Discriminants
(Etype
(Expr_Q
))
5334 end Component_Not_OK_For_Backend
;
5336 -----------------------------------
5337 -- Has_Visible_Private_Ancestor --
5338 -----------------------------------
5340 function Has_Visible_Private_Ancestor
(Id
: E
) return Boolean is
5341 R
: constant Entity_Id
:= Root_Type
(Id
);
5342 T1
: Entity_Id
:= Id
;
5346 if Is_Private_Type
(T1
) then
5356 end Has_Visible_Private_Ancestor
;
5358 -------------------------
5359 -- Top_Level_Aggregate --
5360 -------------------------
5362 function Top_Level_Aggregate
(N
: Node_Id
) return Node_Id
is
5367 while Present
(Parent
(Aggr
))
5368 and then Nkind_In
(Parent
(Aggr
), N_Component_Association
,
5371 Aggr
:= Parent
(Aggr
);
5375 end Top_Level_Aggregate
;
5379 Top_Level_Aggr
: constant Node_Id
:= Top_Level_Aggregate
(N
);
5380 Tag_Value
: Node_Id
;
5384 -- Start of processing for Expand_Record_Aggregate
5387 -- If the aggregate is to be assigned to an atomic variable, we
5388 -- have to prevent a piecemeal assignment even if the aggregate
5389 -- is to be expanded. We create a temporary for the aggregate, and
5390 -- assign the temporary instead, so that the back end can generate
5391 -- an atomic move for it.
5394 and then Comes_From_Source
(Parent
(N
))
5395 and then Is_Atomic_Aggregate
(N
, Typ
)
5399 -- No special management required for aggregates used to initialize
5400 -- statically allocated dispatch tables
5402 elsif Is_Static_Dispatch_Table_Aggregate
(N
) then
5406 -- Ada 2005 (AI-318-2): We need to convert to assignments if components
5407 -- are build-in-place function calls. The assignments will each turn
5408 -- into a build-in-place function call. If components are all static,
5409 -- we can pass the aggregate to the backend regardless of limitedness.
5411 -- Extension aggregates, aggregates in extended return statements, and
5412 -- aggregates for C++ imported types must be expanded.
5414 if Ada_Version
>= Ada_2005
and then Is_Immutably_Limited_Type
(Typ
) then
5415 if not Nkind_In
(Parent
(N
), N_Object_Declaration
,
5416 N_Component_Association
)
5418 Convert_To_Assignments
(N
, Typ
);
5420 elsif Nkind
(N
) = N_Extension_Aggregate
5421 or else Convention
(Typ
) = Convention_CPP
5423 Convert_To_Assignments
(N
, Typ
);
5425 elsif not Size_Known_At_Compile_Time
(Typ
)
5426 or else Component_Not_OK_For_Backend
5427 or else not Static_Components
5429 Convert_To_Assignments
(N
, Typ
);
5432 Set_Compile_Time_Known_Aggregate
(N
);
5433 Set_Expansion_Delayed
(N
, False);
5436 -- Gigi doesn't properly handle temporaries of variable size so we
5437 -- generate it in the front-end
5439 elsif not Size_Known_At_Compile_Time
(Typ
)
5440 and then Tagged_Type_Expansion
5442 Convert_To_Assignments
(N
, Typ
);
5444 -- Temporaries for controlled aggregates need to be attached to a final
5445 -- chain in order to be properly finalized, so it has to be created in
5448 elsif Is_Controlled
(Typ
)
5449 or else Has_Controlled_Component
(Base_Type
(Typ
))
5451 Convert_To_Assignments
(N
, Typ
);
5453 -- Ada 2005 (AI-287): In case of default initialized components we
5454 -- convert the aggregate into assignments.
5456 elsif Has_Default_Init_Comps
(N
) then
5457 Convert_To_Assignments
(N
, Typ
);
5461 elsif Component_Not_OK_For_Backend
then
5462 Convert_To_Assignments
(N
, Typ
);
5464 -- If an ancestor is private, some components are not inherited and we
5465 -- cannot expand into a record aggregate.
5467 elsif Has_Visible_Private_Ancestor
(Typ
) then
5468 Convert_To_Assignments
(N
, Typ
);
5470 -- ??? The following was done to compile fxacc00.ads in the ACVCs. Gigi
5471 -- is not able to handle the aggregate for Late_Request.
5473 elsif Is_Tagged_Type
(Typ
) and then Has_Discriminants
(Typ
) then
5474 Convert_To_Assignments
(N
, Typ
);
5476 -- If the tagged types covers interface types we need to initialize all
5477 -- hidden components containing pointers to secondary dispatch tables.
5479 elsif Is_Tagged_Type
(Typ
) and then Has_Interfaces
(Typ
) then
5480 Convert_To_Assignments
(N
, Typ
);
5482 -- If some components are mutable, the size of the aggregate component
5483 -- may be distinct from the default size of the type component, so
5484 -- we need to expand to insure that the back-end copies the proper
5485 -- size of the data. However, if the aggregate is the initial value of
5486 -- a constant, the target is immutable and might be built statically
5487 -- if components are appropriate.
5489 elsif Has_Mutable_Components
(Typ
)
5491 (Nkind
(Parent
(Top_Level_Aggr
)) /= N_Object_Declaration
5492 or else not Constant_Present
(Parent
(Top_Level_Aggr
))
5493 or else not Static_Components
)
5495 Convert_To_Assignments
(N
, Typ
);
5497 -- If the type involved has any non-bit aligned components, then we are
5498 -- not sure that the back end can handle this case correctly.
5500 elsif Type_May_Have_Bit_Aligned_Components
(Typ
) then
5501 Convert_To_Assignments
(N
, Typ
);
5503 -- In all other cases, build a proper aggregate handlable by gigi
5506 if Nkind
(N
) = N_Aggregate
then
5508 -- If the aggregate is static and can be handled by the back-end,
5509 -- nothing left to do.
5511 if Static_Components
then
5512 Set_Compile_Time_Known_Aggregate
(N
);
5513 Set_Expansion_Delayed
(N
, False);
5517 -- If no discriminants, nothing special to do
5519 if not Has_Discriminants
(Typ
) then
5522 -- Case of discriminants present
5524 elsif Is_Derived_Type
(Typ
) then
5526 -- For untagged types, non-stored discriminants are replaced
5527 -- with stored discriminants, which are the ones that gigi uses
5528 -- to describe the type and its components.
5530 Generate_Aggregate_For_Derived_Type
: declare
5531 Constraints
: constant List_Id
:= New_List
;
5532 First_Comp
: Node_Id
;
5533 Discriminant
: Entity_Id
;
5535 Num_Disc
: Int
:= 0;
5536 Num_Gird
: Int
:= 0;
5538 procedure Prepend_Stored_Values
(T
: Entity_Id
);
5539 -- Scan the list of stored discriminants of the type, and add
5540 -- their values to the aggregate being built.
5542 ---------------------------
5543 -- Prepend_Stored_Values --
5544 ---------------------------
5546 procedure Prepend_Stored_Values
(T
: Entity_Id
) is
5548 Discriminant
:= First_Stored_Discriminant
(T
);
5549 while Present
(Discriminant
) loop
5551 Make_Component_Association
(Loc
,
5553 New_List
(New_Occurrence_Of
(Discriminant
, Loc
)),
5557 Get_Discriminant_Value
(
5560 Discriminant_Constraint
(Typ
))));
5562 if No
(First_Comp
) then
5563 Prepend_To
(Component_Associations
(N
), New_Comp
);
5565 Insert_After
(First_Comp
, New_Comp
);
5568 First_Comp
:= New_Comp
;
5569 Next_Stored_Discriminant
(Discriminant
);
5571 end Prepend_Stored_Values
;
5573 -- Start of processing for Generate_Aggregate_For_Derived_Type
5576 -- Remove the associations for the discriminant of derived type
5578 First_Comp
:= First
(Component_Associations
(N
));
5579 while Present
(First_Comp
) loop
5584 (First
(Choices
(Comp
)))) = E_Discriminant
5587 Num_Disc
:= Num_Disc
+ 1;
5591 -- Insert stored discriminant associations in the correct
5592 -- order. If there are more stored discriminants than new
5593 -- discriminants, there is at least one new discriminant that
5594 -- constrains more than one of the stored discriminants. In
5595 -- this case we need to construct a proper subtype of the
5596 -- parent type, in order to supply values to all the
5597 -- components. Otherwise there is one-one correspondence
5598 -- between the constraints and the stored discriminants.
5600 First_Comp
:= Empty
;
5602 Discriminant
:= First_Stored_Discriminant
(Base_Type
(Typ
));
5603 while Present
(Discriminant
) loop
5604 Num_Gird
:= Num_Gird
+ 1;
5605 Next_Stored_Discriminant
(Discriminant
);
5608 -- Case of more stored discriminants than new discriminants
5610 if Num_Gird
> Num_Disc
then
5612 -- Create a proper subtype of the parent type, which is the
5613 -- proper implementation type for the aggregate, and convert
5614 -- it to the intended target type.
5616 Discriminant
:= First_Stored_Discriminant
(Base_Type
(Typ
));
5617 while Present
(Discriminant
) loop
5620 Get_Discriminant_Value
(
5623 Discriminant_Constraint
(Typ
)));
5624 Append
(New_Comp
, Constraints
);
5625 Next_Stored_Discriminant
(Discriminant
);
5629 Make_Subtype_Declaration
(Loc
,
5630 Defining_Identifier
=> Make_Temporary
(Loc
, 'T'),
5631 Subtype_Indication
=>
5632 Make_Subtype_Indication
(Loc
,
5634 New_Occurrence_Of
(Etype
(Base_Type
(Typ
)), Loc
),
5636 Make_Index_Or_Discriminant_Constraint
5637 (Loc
, Constraints
)));
5639 Insert_Action
(N
, Decl
);
5640 Prepend_Stored_Values
(Base_Type
(Typ
));
5642 Set_Etype
(N
, Defining_Identifier
(Decl
));
5645 Rewrite
(N
, Unchecked_Convert_To
(Typ
, N
));
5648 -- Case where we do not have fewer new discriminants than
5649 -- stored discriminants, so in this case we can simply use the
5650 -- stored discriminants of the subtype.
5653 Prepend_Stored_Values
(Typ
);
5655 end Generate_Aggregate_For_Derived_Type
;
5658 if Is_Tagged_Type
(Typ
) then
5660 -- In the tagged case, _parent and _tag component must be created
5662 -- Reset Null_Present unconditionally. Tagged records always have
5663 -- at least one field (the tag or the parent).
5665 Set_Null_Record_Present
(N
, False);
5667 -- When the current aggregate comes from the expansion of an
5668 -- extension aggregate, the parent expr is replaced by an
5669 -- aggregate formed by selected components of this expr.
5671 if Present
(Parent_Expr
)
5672 and then Is_Empty_List
(Comps
)
5674 Comp
:= First_Component_Or_Discriminant
(Typ
);
5675 while Present
(Comp
) loop
5677 -- Skip all expander-generated components
5680 not Comes_From_Source
(Original_Record_Component
(Comp
))
5686 Make_Selected_Component
(Loc
,
5688 Unchecked_Convert_To
(Typ
,
5689 Duplicate_Subexpr
(Parent_Expr
, True)),
5691 Selector_Name
=> New_Occurrence_Of
(Comp
, Loc
));
5694 Make_Component_Association
(Loc
,
5696 New_List
(New_Occurrence_Of
(Comp
, Loc
)),
5700 Analyze_And_Resolve
(New_Comp
, Etype
(Comp
));
5703 Next_Component_Or_Discriminant
(Comp
);
5707 -- Compute the value for the Tag now, if the type is a root it
5708 -- will be included in the aggregate right away, otherwise it will
5709 -- be propagated to the parent aggregate.
5711 if Present
(Orig_Tag
) then
5712 Tag_Value
:= Orig_Tag
;
5713 elsif not Tagged_Type_Expansion
then
5718 (Node
(First_Elmt
(Access_Disp_Table
(Typ
))), Loc
);
5721 -- For a derived type, an aggregate for the parent is formed with
5722 -- all the inherited components.
5724 if Is_Derived_Type
(Typ
) then
5727 First_Comp
: Node_Id
;
5728 Parent_Comps
: List_Id
;
5729 Parent_Aggr
: Node_Id
;
5730 Parent_Name
: Node_Id
;
5733 -- Remove the inherited component association from the
5734 -- aggregate and store them in the parent aggregate
5736 First_Comp
:= First
(Component_Associations
(N
));
5737 Parent_Comps
:= New_List
;
5738 while Present
(First_Comp
)
5739 and then Scope
(Original_Record_Component
(
5740 Entity
(First
(Choices
(First_Comp
))))) /= Base_Typ
5745 Append
(Comp
, Parent_Comps
);
5748 Parent_Aggr
:= Make_Aggregate
(Loc
,
5749 Component_Associations
=> Parent_Comps
);
5750 Set_Etype
(Parent_Aggr
, Etype
(Base_Type
(Typ
)));
5752 -- Find the _parent component
5754 Comp
:= First_Component
(Typ
);
5755 while Chars
(Comp
) /= Name_uParent
loop
5756 Comp
:= Next_Component
(Comp
);
5759 Parent_Name
:= New_Occurrence_Of
(Comp
, Loc
);
5761 -- Insert the parent aggregate
5763 Prepend_To
(Component_Associations
(N
),
5764 Make_Component_Association
(Loc
,
5765 Choices
=> New_List
(Parent_Name
),
5766 Expression
=> Parent_Aggr
));
5768 -- Expand recursively the parent propagating the right Tag
5770 Expand_Record_Aggregate
5771 (Parent_Aggr
, Tag_Value
, Parent_Expr
);
5773 -- The ancestor part may be a nested aggregate that has
5774 -- delayed expansion: recheck now.
5776 if Component_Not_OK_For_Backend
then
5777 Convert_To_Assignments
(N
, Typ
);
5781 -- For a root type, the tag component is added (unless compiling
5782 -- for the VMs, where tags are implicit).
5784 elsif Tagged_Type_Expansion
then
5786 Tag_Name
: constant Node_Id
:=
5787 New_Occurrence_Of
(First_Tag_Component
(Typ
), Loc
);
5788 Typ_Tag
: constant Entity_Id
:= RTE
(RE_Tag
);
5789 Conv_Node
: constant Node_Id
:=
5790 Unchecked_Convert_To
(Typ_Tag
, Tag_Value
);
5793 Set_Etype
(Conv_Node
, Typ_Tag
);
5794 Prepend_To
(Component_Associations
(N
),
5795 Make_Component_Association
(Loc
,
5796 Choices
=> New_List
(Tag_Name
),
5797 Expression
=> Conv_Node
));
5803 end Expand_Record_Aggregate
;
5805 ----------------------------
5806 -- Has_Default_Init_Comps --
5807 ----------------------------
5809 function Has_Default_Init_Comps
(N
: Node_Id
) return Boolean is
5810 Comps
: constant List_Id
:= Component_Associations
(N
);
5814 pragma Assert
(Nkind_In
(N
, N_Aggregate
, N_Extension_Aggregate
));
5820 if Has_Self_Reference
(N
) then
5824 -- Check if any direct component has default initialized components
5827 while Present
(C
) loop
5828 if Box_Present
(C
) then
5835 -- Recursive call in case of aggregate expression
5838 while Present
(C
) loop
5839 Expr
:= Expression
(C
);
5843 Nkind_In
(Expr
, N_Aggregate
, N_Extension_Aggregate
)
5844 and then Has_Default_Init_Comps
(Expr
)
5853 end Has_Default_Init_Comps
;
5855 --------------------------
5856 -- Is_Delayed_Aggregate --
5857 --------------------------
5859 function Is_Delayed_Aggregate
(N
: Node_Id
) return Boolean is
5860 Node
: Node_Id
:= N
;
5861 Kind
: Node_Kind
:= Nkind
(Node
);
5864 if Kind
= N_Qualified_Expression
then
5865 Node
:= Expression
(Node
);
5866 Kind
:= Nkind
(Node
);
5869 if Kind
/= N_Aggregate
and then Kind
/= N_Extension_Aggregate
then
5872 return Expansion_Delayed
(Node
);
5874 end Is_Delayed_Aggregate
;
5876 ----------------------------------------
5877 -- Is_Static_Dispatch_Table_Aggregate --
5878 ----------------------------------------
5880 function Is_Static_Dispatch_Table_Aggregate
(N
: Node_Id
) return Boolean is
5881 Typ
: constant Entity_Id
:= Base_Type
(Etype
(N
));
5884 return Static_Dispatch_Tables
5885 and then Tagged_Type_Expansion
5886 and then RTU_Loaded
(Ada_Tags
)
5888 -- Avoid circularity when rebuilding the compiler
5890 and then Cunit_Entity
(Get_Source_Unit
(N
)) /= RTU_Entity
(Ada_Tags
)
5891 and then (Typ
= RTE
(RE_Dispatch_Table_Wrapper
)
5893 Typ
= RTE
(RE_Address_Array
)
5895 Typ
= RTE
(RE_Type_Specific_Data
)
5897 Typ
= RTE
(RE_Tag_Table
)
5899 (RTE_Available
(RE_Interface_Data
)
5900 and then Typ
= RTE
(RE_Interface_Data
))
5902 (RTE_Available
(RE_Interfaces_Array
)
5903 and then Typ
= RTE
(RE_Interfaces_Array
))
5905 (RTE_Available
(RE_Interface_Data_Element
)
5906 and then Typ
= RTE
(RE_Interface_Data_Element
)));
5907 end Is_Static_Dispatch_Table_Aggregate
;
5909 -----------------------------
5910 -- Is_Two_Dim_Packed_Array --
5911 -----------------------------
5913 function Is_Two_Dim_Packed_Array
(Typ
: Entity_Id
) return Boolean is
5914 C
: constant Int
:= UI_To_Int
(Component_Size
(Typ
));
5916 return Number_Dimensions
(Typ
) = 2
5917 and then Is_Bit_Packed_Array
(Typ
)
5918 and then (C
= 1 or else C
= 2 or else C
= 4);
5919 end Is_Two_Dim_Packed_Array
;
5921 --------------------
5922 -- Late_Expansion --
5923 --------------------
5925 function Late_Expansion
5928 Target
: Node_Id
) return List_Id
5931 if Is_Record_Type
(Etype
(N
)) then
5932 return Build_Record_Aggr_Code
(N
, Typ
, Target
);
5934 else pragma Assert
(Is_Array_Type
(Etype
(N
)));
5936 Build_Array_Aggr_Code
5938 Ctype
=> Component_Type
(Etype
(N
)),
5939 Index
=> First_Index
(Typ
),
5941 Scalar_Comp
=> Is_Scalar_Type
(Component_Type
(Typ
)),
5942 Indexes
=> No_List
);
5946 ----------------------------------
5947 -- Make_OK_Assignment_Statement --
5948 ----------------------------------
5950 function Make_OK_Assignment_Statement
5953 Expression
: Node_Id
) return Node_Id
5956 Set_Assignment_OK
(Name
);
5958 return Make_Assignment_Statement
(Sloc
, Name
, Expression
);
5959 end Make_OK_Assignment_Statement
;
5961 -----------------------
5962 -- Number_Of_Choices --
5963 -----------------------
5965 function Number_Of_Choices
(N
: Node_Id
) return Nat
is
5969 Nb_Choices
: Nat
:= 0;
5972 if Present
(Expressions
(N
)) then
5976 Assoc
:= First
(Component_Associations
(N
));
5977 while Present
(Assoc
) loop
5978 Choice
:= First
(Choices
(Assoc
));
5979 while Present
(Choice
) loop
5980 if Nkind
(Choice
) /= N_Others_Choice
then
5981 Nb_Choices
:= Nb_Choices
+ 1;
5991 end Number_Of_Choices
;
5993 ------------------------------------
5994 -- Packed_Array_Aggregate_Handled --
5995 ------------------------------------
5997 -- The current version of this procedure will handle at compile time
5998 -- any array aggregate that meets these conditions:
6000 -- One and two dimensional, bit packed
6001 -- Underlying packed type is modular type
6002 -- Bounds are within 32-bit Int range
6003 -- All bounds and values are static
6005 -- Note: for now, in the 2-D case, we only handle component sizes of
6006 -- 1, 2, 4 (cases where an integral number of elements occupies a byte).
6008 function Packed_Array_Aggregate_Handled
(N
: Node_Id
) return Boolean is
6009 Loc
: constant Source_Ptr
:= Sloc
(N
);
6010 Typ
: constant Entity_Id
:= Etype
(N
);
6011 Ctyp
: constant Entity_Id
:= Component_Type
(Typ
);
6013 Not_Handled
: exception;
6014 -- Exception raised if this aggregate cannot be handled
6017 -- Handle one- or two dimensional bit packed array
6019 if not Is_Bit_Packed_Array
(Typ
)
6020 or else Number_Dimensions
(Typ
) > 2
6025 -- If two-dimensional, check whether it can be folded, and transformed
6026 -- into a one-dimensional aggregate for the Packed_Array_Type of the
6029 if Number_Dimensions
(Typ
) = 2 then
6030 return Two_Dim_Packed_Array_Handled
(N
);
6033 if not Is_Modular_Integer_Type
(Packed_Array_Type
(Typ
)) then
6037 if not Is_Scalar_Type
(Component_Type
(Typ
))
6038 and then Has_Non_Standard_Rep
(Component_Type
(Typ
))
6044 Csiz
: constant Nat
:= UI_To_Int
(Component_Size
(Typ
));
6048 -- Bounds of index type
6052 -- Values of bounds if compile time known
6054 function Get_Component_Val
(N
: Node_Id
) return Uint
;
6055 -- Given a expression value N of the component type Ctyp, returns a
6056 -- value of Csiz (component size) bits representing this value. If
6057 -- the value is non-static or any other reason exists why the value
6058 -- cannot be returned, then Not_Handled is raised.
6060 -----------------------
6061 -- Get_Component_Val --
6062 -----------------------
6064 function Get_Component_Val
(N
: Node_Id
) return Uint
is
6068 -- We have to analyze the expression here before doing any further
6069 -- processing here. The analysis of such expressions is deferred
6070 -- till expansion to prevent some problems of premature analysis.
6072 Analyze_And_Resolve
(N
, Ctyp
);
6074 -- Must have a compile time value. String literals have to be
6075 -- converted into temporaries as well, because they cannot easily
6076 -- be converted into their bit representation.
6078 if not Compile_Time_Known_Value
(N
)
6079 or else Nkind
(N
) = N_String_Literal
6084 Val
:= Expr_Rep_Value
(N
);
6086 -- Adjust for bias, and strip proper number of bits
6088 if Has_Biased_Representation
(Ctyp
) then
6089 Val
:= Val
- Expr_Value
(Type_Low_Bound
(Ctyp
));
6092 return Val
mod Uint_2
** Csiz
;
6093 end Get_Component_Val
;
6095 -- Here we know we have a one dimensional bit packed array
6098 Get_Index_Bounds
(First_Index
(Typ
), Lo
, Hi
);
6100 -- Cannot do anything if bounds are dynamic
6102 if not Compile_Time_Known_Value
(Lo
)
6104 not Compile_Time_Known_Value
(Hi
)
6109 -- Or are silly out of range of int bounds
6111 Lob
:= Expr_Value
(Lo
);
6112 Hib
:= Expr_Value
(Hi
);
6114 if not UI_Is_In_Int_Range
(Lob
)
6116 not UI_Is_In_Int_Range
(Hib
)
6121 -- At this stage we have a suitable aggregate for handling at compile
6122 -- time. The only remaining checks are that the values of expressions
6123 -- in the aggregate are compile-time known (checks are performed by
6124 -- Get_Component_Val, and that any subtypes or ranges are statically
6127 -- If the aggregate is not fully positional at this stage, then
6128 -- convert it to positional form. Either this will fail, in which
6129 -- case we can do nothing, or it will succeed, in which case we have
6130 -- succeeded in handling the aggregate and transforming it into a
6131 -- modular value, or it will stay an aggregate, in which case we
6132 -- have failed to create a packed value for it.
6134 if Present
(Component_Associations
(N
)) then
6135 Convert_To_Positional
6136 (N
, Max_Others_Replicate
=> 64, Handle_Bit_Packed
=> True);
6137 return Nkind
(N
) /= N_Aggregate
;
6140 -- Otherwise we are all positional, so convert to proper value
6143 Lov
: constant Int
:= UI_To_Int
(Lob
);
6144 Hiv
: constant Int
:= UI_To_Int
(Hib
);
6146 Len
: constant Nat
:= Int
'Max (0, Hiv
- Lov
+ 1);
6147 -- The length of the array (number of elements)
6149 Aggregate_Val
: Uint
;
6150 -- Value of aggregate. The value is set in the low order bits of
6151 -- this value. For the little-endian case, the values are stored
6152 -- from low-order to high-order and for the big-endian case the
6153 -- values are stored from high-order to low-order. Note that gigi
6154 -- will take care of the conversions to left justify the value in
6155 -- the big endian case (because of left justified modular type
6156 -- processing), so we do not have to worry about that here.
6159 -- Integer literal for resulting constructed value
6162 -- Shift count from low order for next value
6165 -- Shift increment for loop
6168 -- Next expression from positional parameters of aggregate
6170 Left_Justified
: Boolean;
6171 -- Set True if we are filling the high order bits of the target
6172 -- value (i.e. the value is left justified).
6175 -- For little endian, we fill up the low order bits of the target
6176 -- value. For big endian we fill up the high order bits of the
6177 -- target value (which is a left justified modular value).
6179 Left_Justified
:= Bytes_Big_Endian
;
6181 -- Switch justification if using -gnatd8
6183 if Debug_Flag_8
then
6184 Left_Justified
:= not Left_Justified
;
6187 -- Switch justfification if reverse storage order
6189 if Reverse_Storage_Order
(Base_Type
(Typ
)) then
6190 Left_Justified
:= not Left_Justified
;
6193 if Left_Justified
then
6194 Shift
:= Csiz
* (Len
- 1);
6201 -- Loop to set the values
6204 Aggregate_Val
:= Uint_0
;
6206 Expr
:= First
(Expressions
(N
));
6207 Aggregate_Val
:= Get_Component_Val
(Expr
) * Uint_2
** Shift
;
6209 for J
in 2 .. Len
loop
6210 Shift
:= Shift
+ Incr
;
6213 Aggregate_Val
+ Get_Component_Val
(Expr
) * Uint_2
** Shift
;
6217 -- Now we can rewrite with the proper value
6219 Lit
:= Make_Integer_Literal
(Loc
, Intval
=> Aggregate_Val
);
6220 Set_Print_In_Hex
(Lit
);
6222 -- Construct the expression using this literal. Note that it is
6223 -- important to qualify the literal with its proper modular type
6224 -- since universal integer does not have the required range and
6225 -- also this is a left justified modular type, which is important
6226 -- in the big-endian case.
6229 Unchecked_Convert_To
(Typ
,
6230 Make_Qualified_Expression
(Loc
,
6232 New_Occurrence_Of
(Packed_Array_Type
(Typ
), Loc
),
6233 Expression
=> Lit
)));
6235 Analyze_And_Resolve
(N
, Typ
);
6243 end Packed_Array_Aggregate_Handled
;
6245 ----------------------------
6246 -- Has_Mutable_Components --
6247 ----------------------------
6249 function Has_Mutable_Components
(Typ
: Entity_Id
) return Boolean is
6253 Comp
:= First_Component
(Typ
);
6254 while Present
(Comp
) loop
6255 if Is_Record_Type
(Etype
(Comp
))
6256 and then Has_Discriminants
(Etype
(Comp
))
6257 and then not Is_Constrained
(Etype
(Comp
))
6262 Next_Component
(Comp
);
6266 end Has_Mutable_Components
;
6268 ------------------------------
6269 -- Initialize_Discriminants --
6270 ------------------------------
6272 procedure Initialize_Discriminants
(N
: Node_Id
; Typ
: Entity_Id
) is
6273 Loc
: constant Source_Ptr
:= Sloc
(N
);
6274 Bas
: constant Entity_Id
:= Base_Type
(Typ
);
6275 Par
: constant Entity_Id
:= Etype
(Bas
);
6276 Decl
: constant Node_Id
:= Parent
(Par
);
6280 if Is_Tagged_Type
(Bas
)
6281 and then Is_Derived_Type
(Bas
)
6282 and then Has_Discriminants
(Par
)
6283 and then Has_Discriminants
(Bas
)
6284 and then Number_Discriminants
(Bas
) /= Number_Discriminants
(Par
)
6285 and then Nkind
(Decl
) = N_Full_Type_Declaration
6286 and then Nkind
(Type_Definition
(Decl
)) = N_Record_Definition
6288 (Variant_Part
(Component_List
(Type_Definition
(Decl
))))
6289 and then Nkind
(N
) /= N_Extension_Aggregate
6292 -- Call init proc to set discriminants.
6293 -- There should eventually be a special procedure for this ???
6295 Ref
:= New_Reference_To
(Defining_Identifier
(N
), Loc
);
6296 Insert_Actions_After
(N
,
6297 Build_Initialization_Call
(Sloc
(N
), Ref
, Typ
));
6299 end Initialize_Discriminants
;
6306 (Obj_Type
: Entity_Id
;
6307 Typ
: Entity_Id
) return Boolean
6309 L1
, L2
, H1
, H2
: Node_Id
;
6311 -- No sliding if the type of the object is not established yet, if it is
6312 -- an unconstrained type whose actual subtype comes from the aggregate,
6313 -- or if the two types are identical.
6315 if not Is_Array_Type
(Obj_Type
) then
6318 elsif not Is_Constrained
(Obj_Type
) then
6321 elsif Typ
= Obj_Type
then
6325 -- Sliding can only occur along the first dimension
6327 Get_Index_Bounds
(First_Index
(Typ
), L1
, H1
);
6328 Get_Index_Bounds
(First_Index
(Obj_Type
), L2
, H2
);
6330 if not Is_Static_Expression
(L1
)
6331 or else not Is_Static_Expression
(L2
)
6332 or else not Is_Static_Expression
(H1
)
6333 or else not Is_Static_Expression
(H2
)
6337 return Expr_Value
(L1
) /= Expr_Value
(L2
)
6339 Expr_Value
(H1
) /= Expr_Value
(H2
);
6344 ---------------------------
6345 -- Safe_Slice_Assignment --
6346 ---------------------------
6348 function Safe_Slice_Assignment
(N
: Node_Id
) return Boolean is
6349 Loc
: constant Source_Ptr
:= Sloc
(Parent
(N
));
6350 Pref
: constant Node_Id
:= Prefix
(Name
(Parent
(N
)));
6351 Range_Node
: constant Node_Id
:= Discrete_Range
(Name
(Parent
(N
)));
6359 -- Generate: for J in Range loop Pref (J) := Expr; end loop;
6361 if Comes_From_Source
(N
)
6362 and then No
(Expressions
(N
))
6363 and then Nkind
(First
(Choices
(First
(Component_Associations
(N
)))))
6366 Expr
:= Expression
(First
(Component_Associations
(N
)));
6367 L_J
:= Make_Temporary
(Loc
, 'J');
6370 Make_Iteration_Scheme
(Loc
,
6371 Loop_Parameter_Specification
=>
6372 Make_Loop_Parameter_Specification
6374 Defining_Identifier
=> L_J
,
6375 Discrete_Subtype_Definition
=> Relocate_Node
(Range_Node
)));
6378 Make_Assignment_Statement
(Loc
,
6380 Make_Indexed_Component
(Loc
,
6381 Prefix
=> Relocate_Node
(Pref
),
6382 Expressions
=> New_List
(New_Occurrence_Of
(L_J
, Loc
))),
6383 Expression
=> Relocate_Node
(Expr
));
6385 -- Construct the final loop
6388 Make_Implicit_Loop_Statement
6389 (Node
=> Parent
(N
),
6390 Identifier
=> Empty
,
6391 Iteration_Scheme
=> L_Iter
,
6392 Statements
=> New_List
(L_Body
));
6394 -- Set type of aggregate to be type of lhs in assignment,
6395 -- to suppress redundant length checks.
6397 Set_Etype
(N
, Etype
(Name
(Parent
(N
))));
6399 Rewrite
(Parent
(N
), Stat
);
6400 Analyze
(Parent
(N
));
6406 end Safe_Slice_Assignment
;
6408 ----------------------------------
6409 -- Two_Dim_Packed_Array_Handled --
6410 ----------------------------------
6412 function Two_Dim_Packed_Array_Handled
(N
: Node_Id
) return Boolean is
6413 Loc
: constant Source_Ptr
:= Sloc
(N
);
6414 Typ
: constant Entity_Id
:= Etype
(N
);
6415 Ctyp
: constant Entity_Id
:= Component_Type
(Typ
);
6416 Comp_Size
: constant Int
:= UI_To_Int
(Component_Size
(Typ
));
6417 Packed_Array
: constant Entity_Id
:= Packed_Array_Type
(Base_Type
(Typ
));
6420 -- Expression in original aggregate
6423 -- One-dimensional subaggregate
6427 -- For now, only deal with cases where an integral number of elements
6428 -- fit in a single byte. This includes the most common boolean case.
6430 if not (Comp_Size
= 1 or else
6431 Comp_Size
= 2 or else
6437 Convert_To_Positional
6438 (N
, Max_Others_Replicate
=> 64, Handle_Bit_Packed
=> True);
6440 -- Verify that all components are static
6442 if Nkind
(N
) = N_Aggregate
6443 and then Compile_Time_Known_Aggregate
(N
)
6447 -- The aggregate may have been re-analyzed and converted already
6449 elsif Nkind
(N
) /= N_Aggregate
then
6452 -- If component associations remain, the aggregate is not static
6454 elsif Present
(Component_Associations
(N
)) then
6458 One_Dim
:= First
(Expressions
(N
));
6459 while Present
(One_Dim
) loop
6460 if Present
(Component_Associations
(One_Dim
)) then
6464 One_Comp
:= First
(Expressions
(One_Dim
));
6465 while Present
(One_Comp
) loop
6466 if not Is_OK_Static_Expression
(One_Comp
) then
6477 -- Two-dimensional aggregate is now fully positional so pack one
6478 -- dimension to create a static one-dimensional array, and rewrite
6479 -- as an unchecked conversion to the original type.
6482 Byte_Size
: constant Int
:= UI_To_Int
(Component_Size
(Packed_Array
));
6483 -- The packed array type is a byte array
6486 -- Number of components accumulated in current byte
6489 -- Assembled list of packed values for equivalent aggregate
6492 -- integer value of component
6495 -- Step size for packing
6498 -- Endian-dependent start position for packing
6501 -- Current insertion position
6504 -- Component of packed array being assembled.
6511 -- Account for endianness. See corresponding comment in
6512 -- Packed_Array_Aggregate_Handled concerning the following.
6516 xor Reverse_Storage_Order
(Base_Type
(Typ
))
6518 Init_Shift
:= Byte_Size
- Comp_Size
;
6525 Shift
:= Init_Shift
;
6526 One_Dim
:= First
(Expressions
(N
));
6528 -- Iterate over each subaggregate
6530 while Present
(One_Dim
) loop
6531 One_Comp
:= First
(Expressions
(One_Dim
));
6533 while Present
(One_Comp
) loop
6534 if Packed_Num
= Byte_Size
/ Comp_Size
then
6536 -- Byte is complete, add to list of expressions
6538 Append
(Make_Integer_Literal
(Sloc
(One_Dim
), Val
), Comps
);
6540 Shift
:= Init_Shift
;
6544 Comp_Val
:= Expr_Rep_Value
(One_Comp
);
6546 -- Adjust for bias, and strip proper number of bits
6548 if Has_Biased_Representation
(Ctyp
) then
6549 Comp_Val
:= Comp_Val
- Expr_Value
(Type_Low_Bound
(Ctyp
));
6552 Comp_Val
:= Comp_Val
mod Uint_2
** Comp_Size
;
6553 Val
:= UI_To_Int
(Val
+ Comp_Val
* Uint_2
** Shift
);
6554 Shift
:= Shift
+ Incr
;
6555 One_Comp
:= Next
(One_Comp
);
6556 Packed_Num
:= Packed_Num
+ 1;
6560 One_Dim
:= Next
(One_Dim
);
6563 if Packed_Num
> 0 then
6565 -- Add final incomplete byte if present
6567 Append
(Make_Integer_Literal
(Sloc
(One_Dim
), Val
), Comps
);
6571 Unchecked_Convert_To
(Typ
,
6572 Make_Qualified_Expression
(Loc
,
6573 Subtype_Mark
=> New_Occurrence_Of
(Packed_Array
, Loc
),
6575 Make_Aggregate
(Loc
, Expressions
=> Comps
))));
6576 Analyze_And_Resolve
(N
);
6579 end Two_Dim_Packed_Array_Handled
;
6581 ---------------------
6582 -- Sort_Case_Table --
6583 ---------------------
6585 procedure Sort_Case_Table
(Case_Table
: in out Case_Table_Type
) is
6586 L
: constant Int
:= Case_Table
'First;
6587 U
: constant Int
:= Case_Table
'Last;
6595 T
:= Case_Table
(K
+ 1);
6599 and then Expr_Value
(Case_Table
(J
- 1).Choice_Lo
) >
6600 Expr_Value
(T
.Choice_Lo
)
6602 Case_Table
(J
) := Case_Table
(J
- 1);
6606 Case_Table
(J
) := T
;
6609 end Sort_Case_Table
;
6611 ----------------------------
6612 -- Static_Array_Aggregate --
6613 ----------------------------
6615 function Static_Array_Aggregate
(N
: Node_Id
) return Boolean is
6616 Bounds
: constant Node_Id
:= Aggregate_Bounds
(N
);
6618 Typ
: constant Entity_Id
:= Etype
(N
);
6619 Comp_Type
: constant Entity_Id
:= Component_Type
(Typ
);
6626 if Is_Tagged_Type
(Typ
)
6627 or else Is_Controlled
(Typ
)
6628 or else Is_Packed
(Typ
)
6634 and then Nkind
(Bounds
) = N_Range
6635 and then Nkind
(Low_Bound
(Bounds
)) = N_Integer_Literal
6636 and then Nkind
(High_Bound
(Bounds
)) = N_Integer_Literal
6638 Lo
:= Low_Bound
(Bounds
);
6639 Hi
:= High_Bound
(Bounds
);
6641 if No
(Component_Associations
(N
)) then
6643 -- Verify that all components are static integers
6645 Expr
:= First
(Expressions
(N
));
6646 while Present
(Expr
) loop
6647 if Nkind
(Expr
) /= N_Integer_Literal
then
6657 -- We allow only a single named association, either a static
6658 -- range or an others_clause, with a static expression.
6660 Expr
:= First
(Component_Associations
(N
));
6662 if Present
(Expressions
(N
)) then
6665 elsif Present
(Next
(Expr
)) then
6668 elsif Present
(Next
(First
(Choices
(Expr
)))) then
6672 -- The aggregate is static if all components are literals,
6673 -- or else all its components are static aggregates for the
6674 -- component type. We also limit the size of a static aggregate
6675 -- to prevent runaway static expressions.
6677 if Is_Array_Type
(Comp_Type
)
6678 or else Is_Record_Type
(Comp_Type
)
6680 if Nkind
(Expression
(Expr
)) /= N_Aggregate
6682 not Compile_Time_Known_Aggregate
(Expression
(Expr
))
6687 elsif Nkind
(Expression
(Expr
)) /= N_Integer_Literal
then
6691 if not Aggr_Size_OK
(N
, Typ
) then
6695 -- Create a positional aggregate with the right number of
6696 -- copies of the expression.
6698 Agg
:= Make_Aggregate
(Sloc
(N
), New_List
, No_List
);
6700 for I
in UI_To_Int
(Intval
(Lo
)) .. UI_To_Int
(Intval
(Hi
))
6703 (Expressions
(Agg
), New_Copy
(Expression
(Expr
)));
6705 -- The copied expression must be analyzed and resolved.
6706 -- Besides setting the type, this ensures that static
6707 -- expressions are appropriately marked as such.
6710 (Last
(Expressions
(Agg
)), Component_Type
(Typ
));
6713 Set_Aggregate_Bounds
(Agg
, Bounds
);
6714 Set_Etype
(Agg
, Typ
);
6717 Set_Compile_Time_Known_Aggregate
(N
);
6726 end Static_Array_Aggregate
;