1 ------------------------------------------------------------------------------
3 -- GNAT COMPILER COMPONENTS --
9 -- Copyright (C) 1992-2010, 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_Ch7
; use Exp_Ch7
;
36 with Exp_Ch9
; use Exp_Ch9
;
37 with Exp_Tss
; use Exp_Tss
;
38 with Fname
; use Fname
;
39 with Freeze
; use Freeze
;
40 with Itypes
; use Itypes
;
42 with Namet
; use Namet
;
43 with Nmake
; use Nmake
;
44 with Nlists
; use Nlists
;
46 with Restrict
; use Restrict
;
47 with Rident
; use Rident
;
48 with Rtsfind
; use Rtsfind
;
49 with Ttypes
; use Ttypes
;
51 with Sem_Aux
; use Sem_Aux
;
52 with Sem_Ch3
; use Sem_Ch3
;
53 with Sem_Eval
; use Sem_Eval
;
54 with Sem_Res
; use Sem_Res
;
55 with Sem_Util
; use Sem_Util
;
56 with Sinfo
; use Sinfo
;
57 with Snames
; use Snames
;
58 with Stand
; use Stand
;
59 with Targparm
; use Targparm
;
60 with Tbuild
; use Tbuild
;
61 with Uintp
; use Uintp
;
63 package body Exp_Aggr
is
65 type Case_Bounds
is record
68 Choice_Node
: Node_Id
;
71 type Case_Table_Type
is array (Nat
range <>) of Case_Bounds
;
72 -- Table type used by Check_Case_Choices procedure
75 (Obj_Type
: Entity_Id
;
76 Typ
: Entity_Id
) return Boolean;
77 -- A static array aggregate in an object declaration can in most cases be
78 -- expanded in place. The one exception is when the aggregate is given
79 -- with component associations that specify different bounds from those of
80 -- the type definition in the object declaration. In this pathological
81 -- case the aggregate must slide, and we must introduce an intermediate
82 -- temporary to hold it.
84 -- The same holds in an assignment to one-dimensional array of arrays,
85 -- when a component may be given with bounds that differ from those of the
88 procedure Sort_Case_Table
(Case_Table
: in out Case_Table_Type
);
89 -- Sort the Case Table using the Lower Bound of each Choice as the key.
90 -- A simple insertion sort is used since the number of choices in a case
91 -- statement of variant part will usually be small and probably in near
94 function Has_Default_Init_Comps
(N
: Node_Id
) return Boolean;
95 -- N is an aggregate (record or array). Checks the presence of default
96 -- initialization (<>) in any component (Ada 2005: AI-287).
98 function Is_Static_Dispatch_Table_Aggregate
(N
: Node_Id
) return Boolean;
99 -- Returns true if N is an aggregate used to initialize the components
100 -- of an statically allocated dispatch table.
102 ------------------------------------------------------
103 -- Local subprograms for Record Aggregate Expansion --
104 ------------------------------------------------------
106 procedure Expand_Record_Aggregate
108 Orig_Tag
: Node_Id
:= Empty
;
109 Parent_Expr
: Node_Id
:= Empty
);
110 -- This is the top level procedure for record aggregate expansion.
111 -- Expansion for record aggregates needs expand aggregates for tagged
112 -- record types. Specifically Expand_Record_Aggregate adds the Tag
113 -- field in front of the Component_Association list that was created
114 -- during resolution by Resolve_Record_Aggregate.
116 -- N is the record aggregate node.
117 -- Orig_Tag is the value of the Tag that has to be provided for this
118 -- specific aggregate. It carries the tag corresponding to the type
119 -- of the outermost aggregate during the recursive expansion
120 -- Parent_Expr is the ancestor part of the original extension
123 procedure Convert_To_Assignments
(N
: Node_Id
; Typ
: Entity_Id
);
124 -- N is an N_Aggregate or an N_Extension_Aggregate. Typ is the type of the
125 -- aggregate (which can only be a record type, this procedure is only used
126 -- for record types). Transform the given aggregate into a sequence of
127 -- assignments performed component by component.
129 function Build_Record_Aggr_Code
133 Flist
: Node_Id
:= Empty
;
134 Obj
: Entity_Id
:= Empty
;
135 Is_Limited_Ancestor_Expansion
: Boolean := False) return List_Id
;
136 -- N is an N_Aggregate or an N_Extension_Aggregate. Typ is the type of the
137 -- aggregate. Target is an expression containing the location on which the
138 -- component by component assignments will take place. Returns the list of
139 -- assignments plus all other adjustments needed for tagged and controlled
140 -- types. Flist is an expression representing the finalization list on
141 -- which to attach the controlled components if any. Obj is present in the
142 -- object declaration and dynamic allocation cases, it contains an entity
143 -- that allows to know if the value being created needs to be attached to
144 -- the final list in case of pragma Finalize_Storage_Only.
147 -- The meaning of the Obj formal is extremely unclear. *What* entity
148 -- should be passed? For the object declaration case we may guess that
149 -- this is the object being declared, but what about the allocator case?
151 -- Is_Limited_Ancestor_Expansion indicates that the function has been
152 -- called recursively to expand the limited ancestor to avoid copying it.
154 function Has_Mutable_Components
(Typ
: Entity_Id
) return Boolean;
155 -- Return true if one of the component is of a discriminated type with
156 -- defaults. An aggregate for a type with mutable components must be
157 -- expanded into individual assignments.
159 procedure Initialize_Discriminants
(N
: Node_Id
; Typ
: Entity_Id
);
160 -- If the type of the aggregate is a type extension with renamed discrimi-
161 -- nants, we must initialize the hidden discriminants of the parent.
162 -- Otherwise, the target object must not be initialized. The discriminants
163 -- are initialized by calling the initialization procedure for the type.
164 -- This is incorrect if the initialization of other components has any
165 -- side effects. We restrict this call to the case where the parent type
166 -- has a variant part, because this is the only case where the hidden
167 -- discriminants are accessed, namely when calling discriminant checking
168 -- functions of the parent type, and when applying a stream attribute to
169 -- an object of the derived type.
171 -----------------------------------------------------
172 -- Local Subprograms for Array Aggregate Expansion --
173 -----------------------------------------------------
175 function Aggr_Size_OK
(N
: Node_Id
; Typ
: Entity_Id
) return Boolean;
176 -- Very large static aggregates present problems to the back-end, and are
177 -- transformed into assignments and loops. This function verifies that the
178 -- total number of components of an aggregate is acceptable for rewriting
179 -- into a purely positional static form. Aggr_Size_OK must be called before
182 -- This function also detects and warns about one-component aggregates that
183 -- appear in a non-static context. Even if the component value is static,
184 -- such an aggregate must be expanded into an assignment.
186 procedure Convert_Array_Aggr_In_Allocator
190 -- If the aggregate appears within an allocator and can be expanded in
191 -- place, this routine generates the individual assignments to components
192 -- of the designated object. This is an optimization over the general
193 -- case, where a temporary is first created on the stack and then used to
194 -- construct the allocated object on the heap.
196 procedure Convert_To_Positional
198 Max_Others_Replicate
: Nat
:= 5;
199 Handle_Bit_Packed
: Boolean := False);
200 -- If possible, convert named notation to positional notation. This
201 -- conversion is possible only in some static cases. If the conversion is
202 -- possible, then N is rewritten with the analyzed converted aggregate.
203 -- The parameter Max_Others_Replicate controls the maximum number of
204 -- values corresponding to an others choice that will be converted to
205 -- positional notation (the default of 5 is the normal limit, and reflects
206 -- the fact that normally the loop is better than a lot of separate
207 -- assignments). Note that this limit gets overridden in any case if
208 -- either of the restrictions No_Elaboration_Code or No_Implicit_Loops is
209 -- set. The parameter Handle_Bit_Packed is usually set False (since we do
210 -- not expect the back end to handle bit packed arrays, so the normal case
211 -- of conversion is pointless), but in the special case of a call from
212 -- Packed_Array_Aggregate_Handled, we set this parameter to True, since
213 -- these are cases we handle in there.
215 procedure Expand_Array_Aggregate
(N
: Node_Id
);
216 -- This is the top-level routine to perform array aggregate expansion.
217 -- N is the N_Aggregate node to be expanded.
219 function Backend_Processing_Possible
(N
: Node_Id
) return Boolean;
220 -- This function checks if array aggregate N can be processed directly
221 -- by the backend. If this is the case True is returned.
223 function Build_Array_Aggr_Code
228 Scalar_Comp
: Boolean;
229 Indices
: List_Id
:= No_List
;
230 Flist
: Node_Id
:= Empty
) return List_Id
;
231 -- This recursive routine returns a list of statements containing the
232 -- loops and assignments that are needed for the expansion of the array
235 -- N is the (sub-)aggregate node to be expanded into code. This node
236 -- has been fully analyzed, and its Etype is properly set.
238 -- Index is the index node corresponding to the array sub-aggregate N.
240 -- Into is the target expression into which we are copying the aggregate.
241 -- Note that this node may not have been analyzed yet, and so the Etype
242 -- field may not be set.
244 -- Scalar_Comp is True if the component type of the aggregate is scalar.
246 -- Indices is the current list of expressions used to index the
247 -- object we are writing into.
249 -- Flist is an expression representing the finalization list on which
250 -- to attach the controlled components if any.
252 function Number_Of_Choices
(N
: Node_Id
) return Nat
;
253 -- Returns the number of discrete choices (not including the others choice
254 -- if present) contained in (sub-)aggregate N.
256 function Late_Expansion
260 Flist
: Node_Id
:= Empty
;
261 Obj
: Entity_Id
:= Empty
) return List_Id
;
262 -- N is a nested (record or array) aggregate that has been marked with
263 -- 'Delay_Expansion'. Typ is the expected type of the aggregate and Target
264 -- is a (duplicable) expression that will hold the result of the aggregate
265 -- expansion. Flist is the finalization list to be used to attach
266 -- controlled components. 'Obj' when non empty, carries the original
267 -- object being initialized in order to know if it needs to be attached to
268 -- the previous parameter which may not be the case in the case where
269 -- Finalize_Storage_Only is set. Basically this procedure is used to
270 -- implement top-down expansions of nested aggregates. This is necessary
271 -- for avoiding temporaries at each level as well as for propagating the
272 -- right internal finalization list.
274 function Make_OK_Assignment_Statement
277 Expression
: Node_Id
) return Node_Id
;
278 -- This is like Make_Assignment_Statement, except that Assignment_OK
279 -- is set in the left operand. All assignments built by this unit
280 -- use this routine. This is needed to deal with assignments to
281 -- initialized constants that are done in place.
283 function Packed_Array_Aggregate_Handled
(N
: Node_Id
) return Boolean;
284 -- Given an array aggregate, this function handles the case of a packed
285 -- array aggregate with all constant values, where the aggregate can be
286 -- evaluated at compile time. If this is possible, then N is rewritten
287 -- to be its proper compile time value with all the components properly
288 -- assembled. The expression is analyzed and resolved and True is
289 -- returned. If this transformation is not possible, N is unchanged
290 -- and False is returned
292 function Safe_Slice_Assignment
(N
: Node_Id
) return Boolean;
293 -- If a slice assignment has an aggregate with a single others_choice,
294 -- the assignment can be done in place even if bounds are not static,
295 -- by converting it into a loop over the discrete range of the slice.
301 function Aggr_Size_OK
(N
: Node_Id
; Typ
: Entity_Id
) return Boolean is
309 -- The following constant determines the maximum size of an
310 -- array aggregate produced by converting named to positional
311 -- notation (e.g. from others clauses). This avoids running
312 -- away with attempts to convert huge aggregates, which hit
313 -- memory limits in the backend.
315 -- The normal limit is 5000, but we increase this limit to
316 -- 2**24 (about 16 million) if Restrictions (No_Elaboration_Code)
317 -- or Restrictions (No_Implicit_Loops) is specified, since in
318 -- either case, we are at risk of declaring the program illegal
319 -- because of this limit.
321 Max_Aggr_Size
: constant Nat
:=
322 5000 + (2 ** 24 - 5000) *
324 (Restriction_Active
(No_Elaboration_Code
)
326 Restriction_Active
(No_Implicit_Loops
));
328 function Component_Count
(T
: Entity_Id
) return Int
;
329 -- The limit is applied to the total number of components that the
330 -- aggregate will have, which is the number of static expressions
331 -- that will appear in the flattened array. This requires a recursive
332 -- computation of the number of scalar components of the structure.
334 ---------------------
335 -- Component_Count --
336 ---------------------
338 function Component_Count
(T
: Entity_Id
) return Int
is
343 if Is_Scalar_Type
(T
) then
346 elsif Is_Record_Type
(T
) then
347 Comp
:= First_Component
(T
);
348 while Present
(Comp
) loop
349 Res
:= Res
+ Component_Count
(Etype
(Comp
));
350 Next_Component
(Comp
);
355 elsif Is_Array_Type
(T
) then
357 Lo
: constant Node_Id
:=
358 Type_Low_Bound
(Etype
(First_Index
(T
)));
359 Hi
: constant Node_Id
:=
360 Type_High_Bound
(Etype
(First_Index
(T
)));
362 Siz
: constant Int
:= Component_Count
(Component_Type
(T
));
365 if not Compile_Time_Known_Value
(Lo
)
366 or else not Compile_Time_Known_Value
(Hi
)
371 Siz
* UI_To_Int
(Expr_Value
(Hi
) - Expr_Value
(Lo
) + 1);
376 -- Can only be a null for an access type
382 -- Start of processing for Aggr_Size_OK
385 Siz
:= Component_Count
(Component_Type
(Typ
));
387 Indx
:= First_Index
(Typ
);
388 while Present
(Indx
) loop
389 Lo
:= Type_Low_Bound
(Etype
(Indx
));
390 Hi
:= Type_High_Bound
(Etype
(Indx
));
392 -- Bounds need to be known at compile time
394 if not Compile_Time_Known_Value
(Lo
)
395 or else not Compile_Time_Known_Value
(Hi
)
400 Lov
:= Expr_Value
(Lo
);
401 Hiv
:= Expr_Value
(Hi
);
403 -- A flat array is always safe
409 -- One-component aggregates are suspicious, and if the context type
410 -- is an object declaration with non-static bounds it will trip gcc;
411 -- such an aggregate must be expanded into a single assignment.
414 and then Nkind
(Parent
(N
)) = N_Object_Declaration
417 Index_Type
: constant Entity_Id
:=
420 (Etype
(Defining_Identifier
(Parent
(N
)))));
424 if not Compile_Time_Known_Value
(Type_Low_Bound
(Index_Type
))
425 or else not Compile_Time_Known_Value
426 (Type_High_Bound
(Index_Type
))
428 if Present
(Component_Associations
(N
)) then
430 First
(Choices
(First
(Component_Associations
(N
))));
431 if Is_Entity_Name
(Indx
)
432 and then not Is_Type
(Entity
(Indx
))
435 ("single component aggregate in non-static context?",
437 Error_Msg_N
("\maybe subtype name was meant?", Indx
);
447 Rng
: constant Uint
:= Hiv
- Lov
+ 1;
450 -- Check if size is too large
452 if not UI_Is_In_Int_Range
(Rng
) then
456 Siz
:= Siz
* UI_To_Int
(Rng
);
460 or else Siz
> Max_Aggr_Size
465 -- Bounds must be in integer range, for later array construction
467 if not UI_Is_In_Int_Range
(Lov
)
469 not UI_Is_In_Int_Range
(Hiv
)
480 ---------------------------------
481 -- Backend_Processing_Possible --
482 ---------------------------------
484 -- Backend processing by Gigi/gcc is possible only if all the following
485 -- conditions are met:
487 -- 1. N is fully positional
489 -- 2. N is not a bit-packed array aggregate;
491 -- 3. The size of N's array type must be known at compile time. Note
492 -- that this implies that the component size is also known
494 -- 4. The array type of N does not follow the Fortran layout convention
495 -- or if it does it must be 1 dimensional.
497 -- 5. The array component type may not be tagged (which could necessitate
498 -- reassignment of proper tags).
500 -- 6. The array component type must not have unaligned bit components
502 -- 7. None of the components of the aggregate may be bit unaligned
505 -- 8. There cannot be delayed components, since we do not know enough
506 -- at this stage to know if back end processing is possible.
508 -- 9. There cannot be any discriminated record components, since the
509 -- back end cannot handle this complex case.
511 -- 10. No controlled actions need to be generated for components
513 -- 11. For a VM back end, the array should have no aliased components
515 function Backend_Processing_Possible
(N
: Node_Id
) return Boolean is
516 Typ
: constant Entity_Id
:= Etype
(N
);
517 -- Typ is the correct constrained array subtype of the aggregate
519 function Component_Check
(N
: Node_Id
; Index
: Node_Id
) return Boolean;
520 -- This routine checks components of aggregate N, enforcing checks
521 -- 1, 7, 8, and 9. In the multi-dimensional case, these checks are
522 -- performed on subaggregates. The Index value is the current index
523 -- being checked in the multi-dimensional case.
525 ---------------------
526 -- Component_Check --
527 ---------------------
529 function Component_Check
(N
: Node_Id
; Index
: Node_Id
) return Boolean is
533 -- Checks 1: (no component associations)
535 if Present
(Component_Associations
(N
)) then
539 -- Checks on components
541 -- Recurse to check subaggregates, which may appear in qualified
542 -- expressions. If delayed, the front-end will have to expand.
543 -- If the component is a discriminated record, treat as non-static,
544 -- as the back-end cannot handle this properly.
546 Expr
:= First
(Expressions
(N
));
547 while Present
(Expr
) loop
549 -- Checks 8: (no delayed components)
551 if Is_Delayed_Aggregate
(Expr
) then
555 -- Checks 9: (no discriminated records)
557 if Present
(Etype
(Expr
))
558 and then Is_Record_Type
(Etype
(Expr
))
559 and then Has_Discriminants
(Etype
(Expr
))
564 -- Checks 7. Component must not be bit aligned component
566 if Possible_Bit_Aligned_Component
(Expr
) then
570 -- Recursion to following indexes for multiple dimension case
572 if Present
(Next_Index
(Index
))
573 and then not Component_Check
(Expr
, Next_Index
(Index
))
578 -- All checks for that component finished, on to next
586 -- Start of processing for Backend_Processing_Possible
589 -- Checks 2 (array not bit packed) and 10 (no controlled actions)
591 if Is_Bit_Packed_Array
(Typ
) or else Needs_Finalization
(Typ
) then
595 -- If component is limited, aggregate must be expanded because each
596 -- component assignment must be built in place.
598 if Is_Inherently_Limited_Type
(Component_Type
(Typ
)) then
602 -- Checks 4 (array must not be multi-dimensional Fortran case)
604 if Convention
(Typ
) = Convention_Fortran
605 and then Number_Dimensions
(Typ
) > 1
610 -- Checks 3 (size of array must be known at compile time)
612 if not Size_Known_At_Compile_Time
(Typ
) then
616 -- Checks on components
618 if not Component_Check
(N
, First_Index
(Typ
)) then
622 -- Checks 5 (if the component type is tagged, then we may need to do
623 -- tag adjustments. Perhaps this should be refined to check for any
624 -- component associations that actually need tag adjustment, similar
625 -- to the test in Component_Not_OK_For_Backend for record aggregates
626 -- with tagged components, but not clear whether it's worthwhile ???;
627 -- in the case of the JVM, object tags are handled implicitly)
629 if Is_Tagged_Type
(Component_Type
(Typ
))
630 and then Tagged_Type_Expansion
635 -- Checks 6 (component type must not have bit aligned components)
637 if Type_May_Have_Bit_Aligned_Components
(Component_Type
(Typ
)) then
641 -- Checks 11: Array aggregates with aliased components are currently
642 -- not well supported by the VM backend; disable temporarily this
643 -- backend processing until it is definitely supported.
645 if VM_Target
/= No_VM
646 and then Has_Aliased_Components
(Base_Type
(Typ
))
651 -- Backend processing is possible
653 Set_Size_Known_At_Compile_Time
(Etype
(N
), True);
655 end Backend_Processing_Possible
;
657 ---------------------------
658 -- Build_Array_Aggr_Code --
659 ---------------------------
661 -- The code that we generate from a one dimensional aggregate is
663 -- 1. If the sub-aggregate contains discrete choices we
665 -- (a) Sort the discrete choices
667 -- (b) Otherwise for each discrete choice that specifies a range we
668 -- emit a loop. If a range specifies a maximum of three values, or
669 -- we are dealing with an expression we emit a sequence of
670 -- assignments instead of a loop.
672 -- (c) Generate the remaining loops to cover the others choice if any
674 -- 2. If the aggregate contains positional elements we
676 -- (a) translate the positional elements in a series of assignments
678 -- (b) Generate a final loop to cover the others choice if any.
679 -- Note that this final loop has to be a while loop since the case
681 -- L : Integer := Integer'Last;
682 -- H : Integer := Integer'Last;
683 -- A : array (L .. H) := (1, others =>0);
685 -- cannot be handled by a for loop. Thus for the following
687 -- array (L .. H) := (.. positional elements.., others =>E);
689 -- we always generate something like:
691 -- J : Index_Type := Index_Of_Last_Positional_Element;
693 -- J := Index_Base'Succ (J)
697 function Build_Array_Aggr_Code
702 Scalar_Comp
: Boolean;
703 Indices
: List_Id
:= No_List
;
704 Flist
: Node_Id
:= Empty
) return List_Id
706 Loc
: constant Source_Ptr
:= Sloc
(N
);
707 Index_Base
: constant Entity_Id
:= Base_Type
(Etype
(Index
));
708 Index_Base_L
: constant Node_Id
:= Type_Low_Bound
(Index_Base
);
709 Index_Base_H
: constant Node_Id
:= Type_High_Bound
(Index_Base
);
711 function Add
(Val
: Int
; To
: Node_Id
) return Node_Id
;
712 -- Returns an expression where Val is added to expression To, unless
713 -- To+Val is provably out of To's base type range. To must be an
714 -- already analyzed expression.
716 function Empty_Range
(L
, H
: Node_Id
) return Boolean;
717 -- Returns True if the range defined by L .. H is certainly empty
719 function Equal
(L
, H
: Node_Id
) return Boolean;
720 -- Returns True if L = H for sure
722 function Index_Base_Name
return Node_Id
;
723 -- Returns a new reference to the index type name
725 function Gen_Assign
(Ind
: Node_Id
; Expr
: Node_Id
) return List_Id
;
726 -- Ind must be a side-effect free expression. If the input aggregate
727 -- N to Build_Loop contains no sub-aggregates, then this function
728 -- returns the assignment statement:
730 -- Into (Indices, Ind) := Expr;
732 -- Otherwise we call Build_Code recursively
734 -- Ada 2005 (AI-287): In case of default initialized component, Expr
735 -- is empty and we generate a call to the corresponding IP subprogram.
737 function Gen_Loop
(L
, H
: Node_Id
; Expr
: Node_Id
) return List_Id
;
738 -- Nodes L and H must be side-effect free expressions.
739 -- If the input aggregate N to Build_Loop contains no sub-aggregates,
740 -- This routine returns the for loop statement
742 -- for J in Index_Base'(L) .. Index_Base'(H) loop
743 -- Into (Indices, J) := Expr;
746 -- Otherwise we call Build_Code recursively.
747 -- As an optimization if the loop covers 3 or less scalar elements we
748 -- generate a sequence of assignments.
750 function Gen_While
(L
, H
: Node_Id
; Expr
: Node_Id
) return List_Id
;
751 -- Nodes L and H must be side-effect free expressions.
752 -- If the input aggregate N to Build_Loop contains no sub-aggregates,
753 -- This routine returns the while loop statement
755 -- J : Index_Base := L;
757 -- J := Index_Base'Succ (J);
758 -- Into (Indices, J) := Expr;
761 -- Otherwise we call Build_Code recursively
763 function Local_Compile_Time_Known_Value
(E
: Node_Id
) return Boolean;
764 function Local_Expr_Value
(E
: Node_Id
) return Uint
;
765 -- These two Local routines are used to replace the corresponding ones
766 -- in sem_eval because while processing the bounds of an aggregate with
767 -- discrete choices whose index type is an enumeration, we build static
768 -- expressions not recognized by Compile_Time_Known_Value as such since
769 -- they have not yet been analyzed and resolved. All the expressions in
770 -- question are things like Index_Base_Name'Val (Const) which we can
771 -- easily recognize as being constant.
777 function Add
(Val
: Int
; To
: Node_Id
) return Node_Id
is
782 U_Val
: constant Uint
:= UI_From_Int
(Val
);
785 -- Note: do not try to optimize the case of Val = 0, because
786 -- we need to build a new node with the proper Sloc value anyway.
788 -- First test if we can do constant folding
790 if Local_Compile_Time_Known_Value
(To
) then
791 U_To
:= Local_Expr_Value
(To
) + Val
;
793 -- Determine if our constant is outside the range of the index.
794 -- If so return an Empty node. This empty node will be caught
795 -- by Empty_Range below.
797 if Compile_Time_Known_Value
(Index_Base_L
)
798 and then U_To
< Expr_Value
(Index_Base_L
)
802 elsif Compile_Time_Known_Value
(Index_Base_H
)
803 and then U_To
> Expr_Value
(Index_Base_H
)
808 Expr_Pos
:= Make_Integer_Literal
(Loc
, U_To
);
809 Set_Is_Static_Expression
(Expr_Pos
);
811 if not Is_Enumeration_Type
(Index_Base
) then
814 -- If we are dealing with enumeration return
815 -- Index_Base'Val (Expr_Pos)
819 Make_Attribute_Reference
821 Prefix
=> Index_Base_Name
,
822 Attribute_Name
=> Name_Val
,
823 Expressions
=> New_List
(Expr_Pos
));
829 -- If we are here no constant folding possible
831 if not Is_Enumeration_Type
(Index_Base
) then
834 Left_Opnd
=> Duplicate_Subexpr
(To
),
835 Right_Opnd
=> Make_Integer_Literal
(Loc
, U_Val
));
837 -- If we are dealing with enumeration return
838 -- Index_Base'Val (Index_Base'Pos (To) + Val)
842 Make_Attribute_Reference
844 Prefix
=> Index_Base_Name
,
845 Attribute_Name
=> Name_Pos
,
846 Expressions
=> New_List
(Duplicate_Subexpr
(To
)));
851 Right_Opnd
=> Make_Integer_Literal
(Loc
, U_Val
));
854 Make_Attribute_Reference
856 Prefix
=> Index_Base_Name
,
857 Attribute_Name
=> Name_Val
,
858 Expressions
=> New_List
(Expr_Pos
));
868 function Empty_Range
(L
, H
: Node_Id
) return Boolean is
869 Is_Empty
: Boolean := False;
874 -- First check if L or H were already detected as overflowing the
875 -- index base range type by function Add above. If this is so Add
876 -- returns the empty node.
878 if No
(L
) or else No
(H
) then
885 -- L > H range is empty
891 -- B_L > H range must be empty
897 -- L > B_H range must be empty
901 High
:= Index_Base_H
;
904 if Local_Compile_Time_Known_Value
(Low
)
905 and then Local_Compile_Time_Known_Value
(High
)
908 UI_Gt
(Local_Expr_Value
(Low
), Local_Expr_Value
(High
));
921 function Equal
(L
, H
: Node_Id
) return Boolean is
926 elsif Local_Compile_Time_Known_Value
(L
)
927 and then Local_Compile_Time_Known_Value
(H
)
929 return UI_Eq
(Local_Expr_Value
(L
), Local_Expr_Value
(H
));
939 function Gen_Assign
(Ind
: Node_Id
; Expr
: Node_Id
) return List_Id
is
940 L
: constant List_Id
:= New_List
;
944 New_Indices
: List_Id
;
945 Indexed_Comp
: Node_Id
;
947 Comp_Type
: Entity_Id
:= Empty
;
949 function Add_Loop_Actions
(Lis
: List_Id
) return List_Id
;
950 -- Collect insert_actions generated in the construction of a
951 -- loop, and prepend them to the sequence of assignments to
952 -- complete the eventual body of the loop.
954 ----------------------
955 -- Add_Loop_Actions --
956 ----------------------
958 function Add_Loop_Actions
(Lis
: List_Id
) return List_Id
is
962 -- Ada 2005 (AI-287): Do nothing else in case of default
963 -- initialized component.
968 elsif Nkind
(Parent
(Expr
)) = N_Component_Association
969 and then Present
(Loop_Actions
(Parent
(Expr
)))
971 Append_List
(Lis
, Loop_Actions
(Parent
(Expr
)));
972 Res
:= Loop_Actions
(Parent
(Expr
));
973 Set_Loop_Actions
(Parent
(Expr
), No_List
);
979 end Add_Loop_Actions
;
981 -- Start of processing for Gen_Assign
985 New_Indices
:= New_List
;
987 New_Indices
:= New_Copy_List_Tree
(Indices
);
990 Append_To
(New_Indices
, Ind
);
992 if Present
(Flist
) then
993 F
:= New_Copy_Tree
(Flist
);
995 elsif Present
(Etype
(N
)) and then Needs_Finalization
(Etype
(N
)) then
996 if Is_Entity_Name
(Into
)
997 and then Present
(Scope
(Entity
(Into
)))
999 F
:= Find_Final_List
(Scope
(Entity
(Into
)));
1001 F
:= Find_Final_List
(Current_Scope
);
1007 if Present
(Next_Index
(Index
)) then
1010 Build_Array_Aggr_Code
1013 Index
=> Next_Index
(Index
),
1015 Scalar_Comp
=> Scalar_Comp
,
1016 Indices
=> New_Indices
,
1020 -- If we get here then we are at a bottom-level (sub-)aggregate
1024 (Make_Indexed_Component
(Loc
,
1025 Prefix
=> New_Copy_Tree
(Into
),
1026 Expressions
=> New_Indices
));
1028 Set_Assignment_OK
(Indexed_Comp
);
1030 -- Ada 2005 (AI-287): In case of default initialized component, Expr
1031 -- is not present (and therefore we also initialize Expr_Q to empty).
1035 elsif Nkind
(Expr
) = N_Qualified_Expression
then
1036 Expr_Q
:= Expression
(Expr
);
1041 if Present
(Etype
(N
))
1042 and then Etype
(N
) /= Any_Composite
1044 Comp_Type
:= Component_Type
(Etype
(N
));
1045 pragma Assert
(Comp_Type
= Ctype
); -- AI-287
1047 elsif Present
(Next
(First
(New_Indices
))) then
1049 -- Ada 2005 (AI-287): Do nothing in case of default initialized
1050 -- component because we have received the component type in
1051 -- the formal parameter Ctype.
1053 -- ??? Some assert pragmas have been added to check if this new
1054 -- formal can be used to replace this code in all cases.
1056 if Present
(Expr
) then
1058 -- This is a multidimensional array. Recover the component
1059 -- type from the outermost aggregate, because subaggregates
1060 -- do not have an assigned type.
1067 while Present
(P
) loop
1068 if Nkind
(P
) = N_Aggregate
1069 and then Present
(Etype
(P
))
1071 Comp_Type
:= Component_Type
(Etype
(P
));
1079 pragma Assert
(Comp_Type
= Ctype
); -- AI-287
1084 -- Ada 2005 (AI-287): We only analyze the expression in case of non-
1085 -- default initialized components (otherwise Expr_Q is not present).
1088 and then Nkind_In
(Expr_Q
, N_Aggregate
, N_Extension_Aggregate
)
1090 -- At this stage the Expression may not have been analyzed yet
1091 -- because the array aggregate code has not been updated to use
1092 -- the Expansion_Delayed flag and avoid analysis altogether to
1093 -- solve the same problem (see Resolve_Aggr_Expr). So let us do
1094 -- the analysis of non-array aggregates now in order to get the
1095 -- value of Expansion_Delayed flag for the inner aggregate ???
1097 if Present
(Comp_Type
) and then not Is_Array_Type
(Comp_Type
) then
1098 Analyze_And_Resolve
(Expr_Q
, Comp_Type
);
1101 if Is_Delayed_Aggregate
(Expr_Q
) then
1103 -- This is either a subaggregate of a multidimentional array,
1104 -- or a component of an array type whose component type is
1105 -- also an array. In the latter case, the expression may have
1106 -- component associations that provide different bounds from
1107 -- those of the component type, and sliding must occur. Instead
1108 -- of decomposing the current aggregate assignment, force the
1109 -- re-analysis of the assignment, so that a temporary will be
1110 -- generated in the usual fashion, and sliding will take place.
1112 if Nkind
(Parent
(N
)) = N_Assignment_Statement
1113 and then Is_Array_Type
(Comp_Type
)
1114 and then Present
(Component_Associations
(Expr_Q
))
1115 and then Must_Slide
(Comp_Type
, Etype
(Expr_Q
))
1117 Set_Expansion_Delayed
(Expr_Q
, False);
1118 Set_Analyzed
(Expr_Q
, False);
1124 Expr_Q
, Etype
(Expr_Q
), Indexed_Comp
, F
));
1129 -- Ada 2005 (AI-287): In case of default initialized component, call
1130 -- the initialization subprogram associated with the component type.
1131 -- If the component type is an access type, add an explicit null
1132 -- assignment, because for the back-end there is an initialization
1133 -- present for the whole aggregate, and no default initialization
1136 -- In addition, if the component type is controlled, we must call
1137 -- its Initialize procedure explicitly, because there is no explicit
1138 -- object creation that will invoke it otherwise.
1141 if Present
(Base_Init_Proc
(Base_Type
(Ctype
)))
1142 or else Has_Task
(Base_Type
(Ctype
))
1145 Build_Initialization_Call
(Loc
,
1146 Id_Ref
=> Indexed_Comp
,
1148 With_Default_Init
=> True));
1150 elsif Is_Access_Type
(Ctype
) then
1152 Make_Assignment_Statement
(Loc
,
1153 Name
=> Indexed_Comp
,
1154 Expression
=> Make_Null
(Loc
)));
1157 if Needs_Finalization
(Ctype
) then
1160 Ref
=> New_Copy_Tree
(Indexed_Comp
),
1162 Flist_Ref
=> Find_Final_List
(Current_Scope
),
1163 With_Attach
=> Make_Integer_Literal
(Loc
, 1)));
1167 -- Now generate the assignment with no associated controlled
1168 -- actions since the target of the assignment may not have been
1169 -- initialized, it is not possible to Finalize it as expected by
1170 -- normal controlled assignment. The rest of the controlled
1171 -- actions are done manually with the proper finalization list
1172 -- coming from the context.
1175 Make_OK_Assignment_Statement
(Loc
,
1176 Name
=> Indexed_Comp
,
1177 Expression
=> New_Copy_Tree
(Expr
));
1179 if Present
(Comp_Type
) and then Needs_Finalization
(Comp_Type
) then
1180 Set_No_Ctrl_Actions
(A
);
1182 -- If this is an aggregate for an array of arrays, each
1183 -- sub-aggregate will be expanded as well, and even with
1184 -- No_Ctrl_Actions the assignments of inner components will
1185 -- require attachment in their assignments to temporaries.
1186 -- These temporaries must be finalized for each subaggregate,
1187 -- to prevent multiple attachments of the same temporary
1188 -- location to same finalization chain (and consequently
1189 -- circular lists). To ensure that finalization takes place
1190 -- for each subaggregate we wrap the assignment in a block.
1192 if Is_Array_Type
(Comp_Type
)
1193 and then Nkind
(Expr
) = N_Aggregate
1196 Make_Block_Statement
(Loc
,
1197 Handled_Statement_Sequence
=>
1198 Make_Handled_Sequence_Of_Statements
(Loc
,
1199 Statements
=> New_List
(A
)));
1205 -- Adjust the tag if tagged (because of possible view
1206 -- conversions), unless compiling for a VM where
1207 -- tags are implicit.
1209 if Present
(Comp_Type
)
1210 and then Is_Tagged_Type
(Comp_Type
)
1211 and then Tagged_Type_Expansion
1214 Make_OK_Assignment_Statement
(Loc
,
1216 Make_Selected_Component
(Loc
,
1217 Prefix
=> New_Copy_Tree
(Indexed_Comp
),
1220 (First_Tag_Component
(Comp_Type
), Loc
)),
1223 Unchecked_Convert_To
(RTE
(RE_Tag
),
1225 (Node
(First_Elmt
(Access_Disp_Table
(Comp_Type
))),
1231 -- Adjust and attach the component to the proper final list, which
1232 -- can be the controller of the outer record object or the final
1233 -- list associated with the scope.
1235 -- If the component is itself an array of controlled types, whose
1236 -- value is given by a sub-aggregate, then the attach calls have
1237 -- been generated when individual subcomponent are assigned, and
1238 -- must not be done again to prevent malformed finalization chains
1239 -- (see comments above, concerning the creation of a block to hold
1240 -- inner finalization actions).
1242 if Present
(Comp_Type
)
1243 and then Needs_Finalization
(Comp_Type
)
1244 and then not Is_Limited_Type
(Comp_Type
)
1246 (Is_Array_Type
(Comp_Type
)
1247 and then Is_Controlled
(Component_Type
(Comp_Type
))
1248 and then Nkind
(Expr
) = N_Aggregate
)
1252 Ref
=> New_Copy_Tree
(Indexed_Comp
),
1255 With_Attach
=> Make_Integer_Literal
(Loc
, 1)));
1259 return Add_Loop_Actions
(L
);
1266 function Gen_Loop
(L
, H
: Node_Id
; Expr
: Node_Id
) return List_Id
is
1276 -- Index_Base'(L) .. Index_Base'(H)
1278 L_Iteration_Scheme
: Node_Id
;
1279 -- L_J in Index_Base'(L) .. Index_Base'(H)
1282 -- The statements to execute in the loop
1284 S
: constant List_Id
:= New_List
;
1285 -- List of statements
1288 -- Copy of expression tree, used for checking purposes
1291 -- If loop bounds define an empty range return the null statement
1293 if Empty_Range
(L
, H
) then
1294 Append_To
(S
, Make_Null_Statement
(Loc
));
1296 -- Ada 2005 (AI-287): Nothing else need to be done in case of
1297 -- default initialized component.
1303 -- The expression must be type-checked even though no component
1304 -- of the aggregate will have this value. This is done only for
1305 -- actual components of the array, not for subaggregates. Do
1306 -- the check on a copy, because the expression may be shared
1307 -- among several choices, some of which might be non-null.
1309 if Present
(Etype
(N
))
1310 and then Is_Array_Type
(Etype
(N
))
1311 and then No
(Next_Index
(Index
))
1313 Expander_Mode_Save_And_Set
(False);
1314 Tcopy
:= New_Copy_Tree
(Expr
);
1315 Set_Parent
(Tcopy
, N
);
1316 Analyze_And_Resolve
(Tcopy
, Component_Type
(Etype
(N
)));
1317 Expander_Mode_Restore
;
1323 -- If loop bounds are the same then generate an assignment
1325 elsif Equal
(L
, H
) then
1326 return Gen_Assign
(New_Copy_Tree
(L
), Expr
);
1328 -- If H - L <= 2 then generate a sequence of assignments when we are
1329 -- processing the bottom most aggregate and it contains scalar
1332 elsif No
(Next_Index
(Index
))
1333 and then Scalar_Comp
1334 and then Local_Compile_Time_Known_Value
(L
)
1335 and then Local_Compile_Time_Known_Value
(H
)
1336 and then Local_Expr_Value
(H
) - Local_Expr_Value
(L
) <= 2
1339 Append_List_To
(S
, Gen_Assign
(New_Copy_Tree
(L
), Expr
));
1340 Append_List_To
(S
, Gen_Assign
(Add
(1, To
=> L
), Expr
));
1342 if Local_Expr_Value
(H
) - Local_Expr_Value
(L
) = 2 then
1343 Append_List_To
(S
, Gen_Assign
(Add
(2, To
=> L
), Expr
));
1349 -- Otherwise construct the loop, starting with the loop index L_J
1351 L_J
:= Make_Temporary
(Loc
, 'J', L
);
1353 -- Construct "L .. H" in Index_Base. We use a qualified expression
1354 -- for the bound to convert to the index base, but we don't need
1355 -- to do that if we already have the base type at hand.
1357 if Etype
(L
) = Index_Base
then
1361 Make_Qualified_Expression
(Loc
,
1362 Subtype_Mark
=> Index_Base_Name
,
1366 if Etype
(H
) = Index_Base
then
1370 Make_Qualified_Expression
(Loc
,
1371 Subtype_Mark
=> Index_Base_Name
,
1380 -- Construct "for L_J in Index_Base range L .. H"
1382 L_Iteration_Scheme
:=
1383 Make_Iteration_Scheme
1385 Loop_Parameter_Specification
=>
1386 Make_Loop_Parameter_Specification
1388 Defining_Identifier
=> L_J
,
1389 Discrete_Subtype_Definition
=> L_Range
));
1391 -- Construct the statements to execute in the loop body
1393 L_Body
:= Gen_Assign
(New_Reference_To
(L_J
, Loc
), Expr
);
1395 -- Construct the final loop
1397 Append_To
(S
, Make_Implicit_Loop_Statement
1399 Identifier
=> Empty
,
1400 Iteration_Scheme
=> L_Iteration_Scheme
,
1401 Statements
=> L_Body
));
1403 -- A small optimization: if the aggregate is initialized with a box
1404 -- and the component type has no initialization procedure, remove the
1405 -- useless empty loop.
1407 if Nkind
(First
(S
)) = N_Loop_Statement
1408 and then Is_Empty_List
(Statements
(First
(S
)))
1410 return New_List
(Make_Null_Statement
(Loc
));
1420 -- The code built is
1422 -- W_J : Index_Base := L;
1423 -- while W_J < H loop
1424 -- W_J := Index_Base'Succ (W);
1428 function Gen_While
(L
, H
: Node_Id
; Expr
: Node_Id
) return List_Id
is
1432 -- W_J : Base_Type := L;
1434 W_Iteration_Scheme
: Node_Id
;
1437 W_Index_Succ
: Node_Id
;
1438 -- Index_Base'Succ (J)
1440 W_Increment
: Node_Id
;
1441 -- W_J := Index_Base'Succ (W)
1443 W_Body
: constant List_Id
:= New_List
;
1444 -- The statements to execute in the loop
1446 S
: constant List_Id
:= New_List
;
1447 -- list of statement
1450 -- If loop bounds define an empty range or are equal return null
1452 if Empty_Range
(L
, H
) or else Equal
(L
, H
) then
1453 Append_To
(S
, Make_Null_Statement
(Loc
));
1457 -- Build the decl of W_J
1459 W_J
:= Make_Temporary
(Loc
, 'J', L
);
1461 Make_Object_Declaration
1463 Defining_Identifier
=> W_J
,
1464 Object_Definition
=> Index_Base_Name
,
1467 -- Theoretically we should do a New_Copy_Tree (L) here, but we know
1468 -- that in this particular case L is a fresh Expr generated by
1469 -- Add which we are the only ones to use.
1471 Append_To
(S
, W_Decl
);
1473 -- Construct " while W_J < H"
1475 W_Iteration_Scheme
:=
1476 Make_Iteration_Scheme
1478 Condition
=> Make_Op_Lt
1480 Left_Opnd
=> New_Reference_To
(W_J
, Loc
),
1481 Right_Opnd
=> New_Copy_Tree
(H
)));
1483 -- Construct the statements to execute in the loop body
1486 Make_Attribute_Reference
1488 Prefix
=> Index_Base_Name
,
1489 Attribute_Name
=> Name_Succ
,
1490 Expressions
=> New_List
(New_Reference_To
(W_J
, Loc
)));
1493 Make_OK_Assignment_Statement
1495 Name
=> New_Reference_To
(W_J
, Loc
),
1496 Expression
=> W_Index_Succ
);
1498 Append_To
(W_Body
, W_Increment
);
1499 Append_List_To
(W_Body
,
1500 Gen_Assign
(New_Reference_To
(W_J
, Loc
), Expr
));
1502 -- Construct the final loop
1504 Append_To
(S
, Make_Implicit_Loop_Statement
1506 Identifier
=> Empty
,
1507 Iteration_Scheme
=> W_Iteration_Scheme
,
1508 Statements
=> W_Body
));
1513 ---------------------
1514 -- Index_Base_Name --
1515 ---------------------
1517 function Index_Base_Name
return Node_Id
is
1519 return New_Reference_To
(Index_Base
, Sloc
(N
));
1520 end Index_Base_Name
;
1522 ------------------------------------
1523 -- Local_Compile_Time_Known_Value --
1524 ------------------------------------
1526 function Local_Compile_Time_Known_Value
(E
: Node_Id
) return Boolean is
1528 return Compile_Time_Known_Value
(E
)
1530 (Nkind
(E
) = N_Attribute_Reference
1531 and then Attribute_Name
(E
) = Name_Val
1532 and then Compile_Time_Known_Value
(First
(Expressions
(E
))));
1533 end Local_Compile_Time_Known_Value
;
1535 ----------------------
1536 -- Local_Expr_Value --
1537 ----------------------
1539 function Local_Expr_Value
(E
: Node_Id
) return Uint
is
1541 if Compile_Time_Known_Value
(E
) then
1542 return Expr_Value
(E
);
1544 return Expr_Value
(First
(Expressions
(E
)));
1546 end Local_Expr_Value
;
1548 -- Build_Array_Aggr_Code Variables
1555 Others_Expr
: Node_Id
:= Empty
;
1556 Others_Box_Present
: Boolean := False;
1558 Aggr_L
: constant Node_Id
:= Low_Bound
(Aggregate_Bounds
(N
));
1559 Aggr_H
: constant Node_Id
:= High_Bound
(Aggregate_Bounds
(N
));
1560 -- The aggregate bounds of this specific sub-aggregate. Note that if
1561 -- the code generated by Build_Array_Aggr_Code is executed then these
1562 -- bounds are OK. Otherwise a Constraint_Error would have been raised.
1564 Aggr_Low
: constant Node_Id
:= Duplicate_Subexpr_No_Checks
(Aggr_L
);
1565 Aggr_High
: constant Node_Id
:= Duplicate_Subexpr_No_Checks
(Aggr_H
);
1566 -- After Duplicate_Subexpr these are side-effect free
1571 Nb_Choices
: Nat
:= 0;
1572 Table
: Case_Table_Type
(1 .. Number_Of_Choices
(N
));
1573 -- Used to sort all the different choice values
1576 -- Number of elements in the positional aggregate
1578 New_Code
: constant List_Id
:= New_List
;
1580 -- Start of processing for Build_Array_Aggr_Code
1583 -- First before we start, a special case. if we have a bit packed
1584 -- array represented as a modular type, then clear the value to
1585 -- zero first, to ensure that unused bits are properly cleared.
1590 and then Is_Bit_Packed_Array
(Typ
)
1591 and then Is_Modular_Integer_Type
(Packed_Array_Type
(Typ
))
1593 Append_To
(New_Code
,
1594 Make_Assignment_Statement
(Loc
,
1595 Name
=> New_Copy_Tree
(Into
),
1597 Unchecked_Convert_To
(Typ
,
1598 Make_Integer_Literal
(Loc
, Uint_0
))));
1601 -- If the component type contains tasks, we need to build a Master
1602 -- entity in the current scope, because it will be needed if build-
1603 -- in-place functions are called in the expanded code.
1605 if Nkind
(Parent
(N
)) = N_Object_Declaration
1606 and then Has_Task
(Typ
)
1608 Build_Master_Entity
(Defining_Identifier
(Parent
(N
)));
1611 -- STEP 1: Process component associations
1613 -- For those associations that may generate a loop, initialize
1614 -- Loop_Actions to collect inserted actions that may be crated.
1616 -- Skip this if no component associations
1618 if No
(Expressions
(N
)) then
1620 -- STEP 1 (a): Sort the discrete choices
1622 Assoc
:= First
(Component_Associations
(N
));
1623 while Present
(Assoc
) loop
1624 Choice
:= First
(Choices
(Assoc
));
1625 while Present
(Choice
) loop
1626 if Nkind
(Choice
) = N_Others_Choice
then
1627 Set_Loop_Actions
(Assoc
, New_List
);
1629 if Box_Present
(Assoc
) then
1630 Others_Box_Present
:= True;
1632 Others_Expr
:= Expression
(Assoc
);
1637 Get_Index_Bounds
(Choice
, Low
, High
);
1640 Set_Loop_Actions
(Assoc
, New_List
);
1643 Nb_Choices
:= Nb_Choices
+ 1;
1644 if Box_Present
(Assoc
) then
1645 Table
(Nb_Choices
) := (Choice_Lo
=> Low
,
1647 Choice_Node
=> Empty
);
1649 Table
(Nb_Choices
) := (Choice_Lo
=> Low
,
1651 Choice_Node
=> Expression
(Assoc
));
1659 -- If there is more than one set of choices these must be static
1660 -- and we can therefore sort them. Remember that Nb_Choices does not
1661 -- account for an others choice.
1663 if Nb_Choices
> 1 then
1664 Sort_Case_Table
(Table
);
1667 -- STEP 1 (b): take care of the whole set of discrete choices
1669 for J
in 1 .. Nb_Choices
loop
1670 Low
:= Table
(J
).Choice_Lo
;
1671 High
:= Table
(J
).Choice_Hi
;
1672 Expr
:= Table
(J
).Choice_Node
;
1673 Append_List
(Gen_Loop
(Low
, High
, Expr
), To
=> New_Code
);
1676 -- STEP 1 (c): generate the remaining loops to cover others choice
1677 -- We don't need to generate loops over empty gaps, but if there is
1678 -- a single empty range we must analyze the expression for semantics
1680 if Present
(Others_Expr
) or else Others_Box_Present
then
1682 First
: Boolean := True;
1685 for J
in 0 .. Nb_Choices
loop
1689 Low
:= Add
(1, To
=> Table
(J
).Choice_Hi
);
1692 if J
= Nb_Choices
then
1695 High
:= Add
(-1, To
=> Table
(J
+ 1).Choice_Lo
);
1698 -- If this is an expansion within an init proc, make
1699 -- sure that discriminant references are replaced by
1700 -- the corresponding discriminal.
1702 if Inside_Init_Proc
then
1703 if Is_Entity_Name
(Low
)
1704 and then Ekind
(Entity
(Low
)) = E_Discriminant
1706 Set_Entity
(Low
, Discriminal
(Entity
(Low
)));
1709 if Is_Entity_Name
(High
)
1710 and then Ekind
(Entity
(High
)) = E_Discriminant
1712 Set_Entity
(High
, Discriminal
(Entity
(High
)));
1717 or else not Empty_Range
(Low
, High
)
1721 (Gen_Loop
(Low
, High
, Others_Expr
), To
=> New_Code
);
1727 -- STEP 2: Process positional components
1730 -- STEP 2 (a): Generate the assignments for each positional element
1731 -- Note that here we have to use Aggr_L rather than Aggr_Low because
1732 -- Aggr_L is analyzed and Add wants an analyzed expression.
1734 Expr
:= First
(Expressions
(N
));
1736 while Present
(Expr
) loop
1737 Nb_Elements
:= Nb_Elements
+ 1;
1738 Append_List
(Gen_Assign
(Add
(Nb_Elements
, To
=> Aggr_L
), Expr
),
1743 -- STEP 2 (b): Generate final loop if an others choice is present
1744 -- Here Nb_Elements gives the offset of the last positional element.
1746 if Present
(Component_Associations
(N
)) then
1747 Assoc
:= Last
(Component_Associations
(N
));
1749 -- Ada 2005 (AI-287)
1751 if Box_Present
(Assoc
) then
1752 Append_List
(Gen_While
(Add
(Nb_Elements
, To
=> Aggr_L
),
1757 Expr
:= Expression
(Assoc
);
1759 Append_List
(Gen_While
(Add
(Nb_Elements
, To
=> Aggr_L
),
1768 end Build_Array_Aggr_Code
;
1770 ----------------------------
1771 -- Build_Record_Aggr_Code --
1772 ----------------------------
1774 function Build_Record_Aggr_Code
1778 Flist
: Node_Id
:= Empty
;
1779 Obj
: Entity_Id
:= Empty
;
1780 Is_Limited_Ancestor_Expansion
: Boolean := False) return List_Id
1782 Loc
: constant Source_Ptr
:= Sloc
(N
);
1783 L
: constant List_Id
:= New_List
;
1784 N_Typ
: constant Entity_Id
:= Etype
(N
);
1791 Comp_Type
: Entity_Id
;
1792 Selector
: Entity_Id
;
1793 Comp_Expr
: Node_Id
;
1796 Internal_Final_List
: Node_Id
:= Empty
;
1798 -- If this is an internal aggregate, the External_Final_List is an
1799 -- expression for the controller record of the enclosing type.
1801 -- If the current aggregate has several controlled components, this
1802 -- expression will appear in several calls to attach to the finali-
1803 -- zation list, and it must not be shared.
1805 External_Final_List
: Node_Id
;
1806 Ancestor_Is_Expression
: Boolean := False;
1807 Ancestor_Is_Subtype_Mark
: Boolean := False;
1809 Init_Typ
: Entity_Id
:= Empty
;
1812 Ctrl_Stuff_Done
: Boolean := False;
1813 -- True if Gen_Ctrl_Actions_For_Aggr has already been called; calls
1814 -- after the first do nothing.
1816 function Ancestor_Discriminant_Value
(Disc
: Entity_Id
) return Node_Id
;
1817 -- Returns the value that the given discriminant of an ancestor type
1818 -- should receive (in the absence of a conflict with the value provided
1819 -- by an ancestor part of an extension aggregate).
1821 procedure Check_Ancestor_Discriminants
(Anc_Typ
: Entity_Id
);
1822 -- Check that each of the discriminant values defined by the ancestor
1823 -- part of an extension aggregate match the corresponding values
1824 -- provided by either an association of the aggregate or by the
1825 -- constraint imposed by a parent type (RM95-4.3.2(8)).
1827 function Compatible_Int_Bounds
1828 (Agg_Bounds
: Node_Id
;
1829 Typ_Bounds
: Node_Id
) return Boolean;
1830 -- Return true if Agg_Bounds are equal or within Typ_Bounds. It is
1831 -- assumed that both bounds are integer ranges.
1833 procedure Gen_Ctrl_Actions_For_Aggr
;
1834 -- Deal with the various controlled type data structure initializations
1835 -- (but only if it hasn't been done already).
1837 function Get_Constraint_Association
(T
: Entity_Id
) return Node_Id
;
1838 -- Returns the first discriminant association in the constraint
1839 -- associated with T, if any, otherwise returns Empty.
1841 function Init_Controller
1846 Init_Pr
: Boolean) return List_Id
;
1847 -- Returns the list of statements necessary to initialize the internal
1848 -- controller of the (possible) ancestor typ into target and attach it
1849 -- to finalization list F. Init_Pr conditions the call to the init proc
1850 -- since it may already be done due to ancestor initialization.
1852 function Is_Int_Range_Bounds
(Bounds
: Node_Id
) return Boolean;
1853 -- Check whether Bounds is a range node and its lower and higher bounds
1854 -- are integers literals.
1856 ---------------------------------
1857 -- Ancestor_Discriminant_Value --
1858 ---------------------------------
1860 function Ancestor_Discriminant_Value
(Disc
: Entity_Id
) return Node_Id
is
1862 Assoc_Elmt
: Elmt_Id
;
1863 Aggr_Comp
: Entity_Id
;
1864 Corresp_Disc
: Entity_Id
;
1865 Current_Typ
: Entity_Id
:= Base_Type
(Typ
);
1866 Parent_Typ
: Entity_Id
;
1867 Parent_Disc
: Entity_Id
;
1868 Save_Assoc
: Node_Id
:= Empty
;
1871 -- First check any discriminant associations to see if any of them
1872 -- provide a value for the discriminant.
1874 if Present
(Discriminant_Specifications
(Parent
(Current_Typ
))) then
1875 Assoc
:= First
(Component_Associations
(N
));
1876 while Present
(Assoc
) loop
1877 Aggr_Comp
:= Entity
(First
(Choices
(Assoc
)));
1879 if Ekind
(Aggr_Comp
) = E_Discriminant
then
1880 Save_Assoc
:= Expression
(Assoc
);
1882 Corresp_Disc
:= Corresponding_Discriminant
(Aggr_Comp
);
1883 while Present
(Corresp_Disc
) loop
1885 -- If found a corresponding discriminant then return the
1886 -- value given in the aggregate. (Note: this is not
1887 -- correct in the presence of side effects. ???)
1889 if Disc
= Corresp_Disc
then
1890 return Duplicate_Subexpr
(Expression
(Assoc
));
1894 Corresponding_Discriminant
(Corresp_Disc
);
1902 -- No match found in aggregate, so chain up parent types to find
1903 -- a constraint that defines the value of the discriminant.
1905 Parent_Typ
:= Etype
(Current_Typ
);
1906 while Current_Typ
/= Parent_Typ
loop
1907 if Has_Discriminants
(Parent_Typ
)
1908 and then not Has_Unknown_Discriminants
(Parent_Typ
)
1910 Parent_Disc
:= First_Discriminant
(Parent_Typ
);
1912 -- We either get the association from the subtype indication
1913 -- of the type definition itself, or from the discriminant
1914 -- constraint associated with the type entity (which is
1915 -- preferable, but it's not always present ???)
1917 if Is_Empty_Elmt_List
(
1918 Discriminant_Constraint
(Current_Typ
))
1920 Assoc
:= Get_Constraint_Association
(Current_Typ
);
1921 Assoc_Elmt
:= No_Elmt
;
1924 First_Elmt
(Discriminant_Constraint
(Current_Typ
));
1925 Assoc
:= Node
(Assoc_Elmt
);
1928 -- Traverse the discriminants of the parent type looking
1929 -- for one that corresponds.
1931 while Present
(Parent_Disc
) and then Present
(Assoc
) loop
1932 Corresp_Disc
:= Parent_Disc
;
1933 while Present
(Corresp_Disc
)
1934 and then Disc
/= Corresp_Disc
1937 Corresponding_Discriminant
(Corresp_Disc
);
1940 if Disc
= Corresp_Disc
then
1941 if Nkind
(Assoc
) = N_Discriminant_Association
then
1942 Assoc
:= Expression
(Assoc
);
1945 -- If the located association directly denotes a
1946 -- discriminant, then use the value of a saved
1947 -- association of the aggregate. This is a kludge to
1948 -- handle certain cases involving multiple discriminants
1949 -- mapped to a single discriminant of a descendant. It's
1950 -- not clear how to locate the appropriate discriminant
1951 -- value for such cases. ???
1953 if Is_Entity_Name
(Assoc
)
1954 and then Ekind
(Entity
(Assoc
)) = E_Discriminant
1956 Assoc
:= Save_Assoc
;
1959 return Duplicate_Subexpr
(Assoc
);
1962 Next_Discriminant
(Parent_Disc
);
1964 if No
(Assoc_Elmt
) then
1967 Next_Elmt
(Assoc_Elmt
);
1968 if Present
(Assoc_Elmt
) then
1969 Assoc
:= Node
(Assoc_Elmt
);
1977 Current_Typ
:= Parent_Typ
;
1978 Parent_Typ
:= Etype
(Current_Typ
);
1981 -- In some cases there's no ancestor value to locate (such as
1982 -- when an ancestor part given by an expression defines the
1983 -- discriminant value).
1986 end Ancestor_Discriminant_Value
;
1988 ----------------------------------
1989 -- Check_Ancestor_Discriminants --
1990 ----------------------------------
1992 procedure Check_Ancestor_Discriminants
(Anc_Typ
: Entity_Id
) is
1994 Disc_Value
: Node_Id
;
1998 Discr
:= First_Discriminant
(Base_Type
(Anc_Typ
));
1999 while Present
(Discr
) loop
2000 Disc_Value
:= Ancestor_Discriminant_Value
(Discr
);
2002 if Present
(Disc_Value
) then
2003 Cond
:= Make_Op_Ne
(Loc
,
2005 Make_Selected_Component
(Loc
,
2006 Prefix
=> New_Copy_Tree
(Target
),
2007 Selector_Name
=> New_Occurrence_Of
(Discr
, Loc
)),
2008 Right_Opnd
=> Disc_Value
);
2011 Make_Raise_Constraint_Error
(Loc
,
2013 Reason
=> CE_Discriminant_Check_Failed
));
2016 Next_Discriminant
(Discr
);
2018 end Check_Ancestor_Discriminants
;
2020 ---------------------------
2021 -- Compatible_Int_Bounds --
2022 ---------------------------
2024 function Compatible_Int_Bounds
2025 (Agg_Bounds
: Node_Id
;
2026 Typ_Bounds
: Node_Id
) return Boolean
2028 Agg_Lo
: constant Uint
:= Intval
(Low_Bound
(Agg_Bounds
));
2029 Agg_Hi
: constant Uint
:= Intval
(High_Bound
(Agg_Bounds
));
2030 Typ_Lo
: constant Uint
:= Intval
(Low_Bound
(Typ_Bounds
));
2031 Typ_Hi
: constant Uint
:= Intval
(High_Bound
(Typ_Bounds
));
2033 return Typ_Lo
<= Agg_Lo
and then Agg_Hi
<= Typ_Hi
;
2034 end Compatible_Int_Bounds
;
2036 --------------------------------
2037 -- Get_Constraint_Association --
2038 --------------------------------
2040 function Get_Constraint_Association
(T
: Entity_Id
) return Node_Id
is
2041 Typ_Def
: constant Node_Id
:= Type_Definition
(Parent
(T
));
2042 Indic
: constant Node_Id
:= Subtype_Indication
(Typ_Def
);
2045 -- ??? Also need to cover case of a type mark denoting a subtype
2048 if Nkind
(Indic
) = N_Subtype_Indication
2049 and then Present
(Constraint
(Indic
))
2051 return First
(Constraints
(Constraint
(Indic
)));
2055 end Get_Constraint_Association
;
2057 ---------------------
2058 -- Init_Controller --
2059 ---------------------
2061 function Init_Controller
2066 Init_Pr
: Boolean) return List_Id
2068 L
: constant List_Id
:= New_List
;
2071 Target_Type
: Entity_Id
;
2075 -- init-proc (target._controller);
2076 -- initialize (target._controller);
2077 -- Attach_to_Final_List (target._controller, F);
2080 Make_Selected_Component
(Loc
,
2081 Prefix
=> Convert_To
(Typ
, New_Copy_Tree
(Target
)),
2082 Selector_Name
=> Make_Identifier
(Loc
, Name_uController
));
2083 Set_Assignment_OK
(Ref
);
2085 -- Ada 2005 (AI-287): Give support to aggregates of limited types.
2086 -- If the type is intrinsically limited the controller is limited as
2087 -- well. If it is tagged and limited then so is the controller.
2088 -- Otherwise an untagged type may have limited components without its
2089 -- full view being limited, so the controller is not limited.
2091 if Nkind
(Target
) = N_Identifier
then
2092 Target_Type
:= Etype
(Target
);
2094 elsif Nkind
(Target
) = N_Selected_Component
then
2095 Target_Type
:= Etype
(Selector_Name
(Target
));
2097 elsif Nkind
(Target
) = N_Unchecked_Type_Conversion
then
2098 Target_Type
:= Etype
(Target
);
2100 elsif Nkind
(Target
) = N_Unchecked_Expression
2101 and then Nkind
(Expression
(Target
)) = N_Indexed_Component
2103 Target_Type
:= Etype
(Prefix
(Expression
(Target
)));
2106 Target_Type
:= Etype
(Target
);
2109 -- If the target has not been analyzed yet, as will happen with
2110 -- delayed expansion, use the given type (either the aggregate type
2111 -- or an ancestor) to determine limitedness.
2113 if No
(Target_Type
) then
2117 if (Is_Tagged_Type
(Target_Type
))
2118 and then Is_Limited_Type
(Target_Type
)
2120 RC
:= RE_Limited_Record_Controller
;
2122 elsif Is_Inherently_Limited_Type
(Target_Type
) then
2123 RC
:= RE_Limited_Record_Controller
;
2126 RC
:= RE_Record_Controller
;
2131 Build_Initialization_Call
(Loc
,
2134 In_Init_Proc
=> Within_Init_Proc
));
2138 Make_Procedure_Call_Statement
(Loc
,
2141 Find_Prim_Op
(RTE
(RC
), Name_Initialize
), Loc
),
2142 Parameter_Associations
=>
2143 New_List
(New_Copy_Tree
(Ref
))));
2147 Obj_Ref
=> New_Copy_Tree
(Ref
),
2149 With_Attach
=> Attach
));
2152 end Init_Controller
;
2154 -------------------------
2155 -- Is_Int_Range_Bounds --
2156 -------------------------
2158 function Is_Int_Range_Bounds
(Bounds
: Node_Id
) return Boolean is
2160 return Nkind
(Bounds
) = N_Range
2161 and then Nkind
(Low_Bound
(Bounds
)) = N_Integer_Literal
2162 and then Nkind
(High_Bound
(Bounds
)) = N_Integer_Literal
;
2163 end Is_Int_Range_Bounds
;
2165 -------------------------------
2166 -- Gen_Ctrl_Actions_For_Aggr --
2167 -------------------------------
2169 procedure Gen_Ctrl_Actions_For_Aggr
is
2170 Alloc
: Node_Id
:= Empty
;
2173 -- Do the work only the first time this is called
2175 if Ctrl_Stuff_Done
then
2179 Ctrl_Stuff_Done
:= True;
2182 and then Finalize_Storage_Only
(Typ
)
2184 (Is_Library_Level_Entity
(Obj
)
2185 or else Entity
(Constant_Value
(RTE
(RE_Garbage_Collected
))) =
2188 -- why not Is_True (Expr_Value (RTE (RE_Garbaage_Collected) ???
2190 Attach
:= Make_Integer_Literal
(Loc
, 0);
2192 elsif Nkind
(Parent
(N
)) = N_Qualified_Expression
2193 and then Nkind
(Parent
(Parent
(N
))) = N_Allocator
2195 Alloc
:= Parent
(Parent
(N
));
2196 Attach
:= Make_Integer_Literal
(Loc
, 2);
2199 Attach
:= Make_Integer_Literal
(Loc
, 1);
2202 -- Determine the external finalization list. It is either the
2203 -- finalization list of the outer-scope or the one coming from
2204 -- an outer aggregate. When the target is not a temporary, the
2205 -- proper scope is the scope of the target rather than the
2206 -- potentially transient current scope.
2208 if Needs_Finalization
(Typ
) then
2210 -- The current aggregate belongs to an allocator which creates
2211 -- an object through an anonymous access type or acts as the root
2212 -- of a coextension chain.
2216 (Is_Coextension_Root
(Alloc
)
2217 or else Ekind
(Etype
(Alloc
)) = E_Anonymous_Access_Type
)
2219 if No
(Associated_Final_Chain
(Etype
(Alloc
))) then
2220 Build_Final_List
(Alloc
, Etype
(Alloc
));
2223 External_Final_List
:=
2224 Make_Selected_Component
(Loc
,
2227 Associated_Final_Chain
(Etype
(Alloc
)), Loc
),
2229 Make_Identifier
(Loc
, Name_F
));
2231 elsif Present
(Flist
) then
2232 External_Final_List
:= New_Copy_Tree
(Flist
);
2234 elsif Is_Entity_Name
(Target
)
2235 and then Present
(Scope
(Entity
(Target
)))
2237 External_Final_List
:=
2238 Find_Final_List
(Scope
(Entity
(Target
)));
2241 External_Final_List
:= Find_Final_List
(Current_Scope
);
2244 External_Final_List
:= Empty
;
2247 -- Initialize and attach the outer object in the is_controlled case
2249 if Is_Controlled
(Typ
) then
2250 if Ancestor_Is_Subtype_Mark
then
2251 Ref
:= Convert_To
(Init_Typ
, New_Copy_Tree
(Target
));
2252 Set_Assignment_OK
(Ref
);
2254 Make_Procedure_Call_Statement
(Loc
,
2257 (Find_Prim_Op
(Init_Typ
, Name_Initialize
), Loc
),
2258 Parameter_Associations
=> New_List
(New_Copy_Tree
(Ref
))));
2261 if not Has_Controlled_Component
(Typ
) then
2262 Ref
:= New_Copy_Tree
(Target
);
2263 Set_Assignment_OK
(Ref
);
2265 -- This is an aggregate of a coextension. Do not produce a
2266 -- finalization call, but rather attach the reference of the
2267 -- aggregate to its coextension chain.
2270 and then Is_Dynamic_Coextension
(Alloc
)
2272 if No
(Coextensions
(Alloc
)) then
2273 Set_Coextensions
(Alloc
, New_Elmt_List
);
2276 Append_Elmt
(Ref
, Coextensions
(Alloc
));
2281 Flist_Ref
=> New_Copy_Tree
(External_Final_List
),
2282 With_Attach
=> Attach
));
2287 -- In the Has_Controlled component case, all the intermediate
2288 -- controllers must be initialized.
2290 if Has_Controlled_Component
(Typ
)
2291 and not Is_Limited_Ancestor_Expansion
2294 Inner_Typ
: Entity_Id
;
2295 Outer_Typ
: Entity_Id
;
2299 -- Find outer type with a controller
2301 Outer_Typ
:= Base_Type
(Typ
);
2302 while Outer_Typ
/= Init_Typ
2303 and then not Has_New_Controlled_Component
(Outer_Typ
)
2305 Outer_Typ
:= Etype
(Outer_Typ
);
2308 -- Attach it to the outer record controller to the external
2311 if Outer_Typ
= Init_Typ
then
2316 F
=> External_Final_List
,
2321 Inner_Typ
:= Init_Typ
;
2328 F
=> External_Final_List
,
2332 Inner_Typ
:= Etype
(Outer_Typ
);
2334 not Is_Tagged_Type
(Typ
) or else Inner_Typ
= Outer_Typ
;
2337 -- The outer object has to be attached as well
2339 if Is_Controlled
(Typ
) then
2340 Ref
:= New_Copy_Tree
(Target
);
2341 Set_Assignment_OK
(Ref
);
2345 Flist_Ref
=> New_Copy_Tree
(External_Final_List
),
2346 With_Attach
=> New_Copy_Tree
(Attach
)));
2349 -- Initialize the internal controllers for tagged types with
2350 -- more than one controller.
2352 while not At_Root
and then Inner_Typ
/= Init_Typ
loop
2353 if Has_New_Controlled_Component
(Inner_Typ
) then
2355 Make_Selected_Component
(Loc
,
2357 Convert_To
(Outer_Typ
, New_Copy_Tree
(Target
)),
2359 Make_Identifier
(Loc
, Name_uController
));
2361 Make_Selected_Component
(Loc
,
2363 Selector_Name
=> Make_Identifier
(Loc
, Name_F
));
2370 Attach
=> Make_Integer_Literal
(Loc
, 1),
2372 Outer_Typ
:= Inner_Typ
;
2377 At_Root
:= Inner_Typ
= Etype
(Inner_Typ
);
2378 Inner_Typ
:= Etype
(Inner_Typ
);
2381 -- If not done yet attach the controller of the ancestor part
2383 if Outer_Typ
/= Init_Typ
2384 and then Inner_Typ
= Init_Typ
2385 and then Has_Controlled_Component
(Init_Typ
)
2388 Make_Selected_Component
(Loc
,
2389 Prefix
=> Convert_To
(Outer_Typ
, New_Copy_Tree
(Target
)),
2391 Make_Identifier
(Loc
, Name_uController
));
2393 Make_Selected_Component
(Loc
,
2395 Selector_Name
=> Make_Identifier
(Loc
, Name_F
));
2397 Attach
:= Make_Integer_Literal
(Loc
, 1);
2406 -- Note: Init_Pr is False because the ancestor part has
2407 -- already been initialized either way (by default, if
2408 -- given by a type name, otherwise from the expression).
2413 end Gen_Ctrl_Actions_For_Aggr
;
2415 function Rewrite_Discriminant
(Expr
: Node_Id
) return Traverse_Result
;
2416 -- If default expression of a component mentions a discriminant of the
2417 -- type, it must be rewritten as the discriminant of the target object.
2419 function Replace_Type
(Expr
: Node_Id
) return Traverse_Result
;
2420 -- If the aggregate contains a self-reference, traverse each expression
2421 -- to replace a possible self-reference with a reference to the proper
2422 -- component of the target of the assignment.
2424 --------------------------
2425 -- Rewrite_Discriminant --
2426 --------------------------
2428 function Rewrite_Discriminant
(Expr
: Node_Id
) return Traverse_Result
is
2430 if Is_Entity_Name
(Expr
)
2431 and then Present
(Entity
(Expr
))
2432 and then Ekind
(Entity
(Expr
)) = E_In_Parameter
2433 and then Present
(Discriminal_Link
(Entity
(Expr
)))
2434 and then Scope
(Discriminal_Link
(Entity
(Expr
)))
2435 = Base_Type
(Etype
(N
))
2438 Make_Selected_Component
(Loc
,
2439 Prefix
=> New_Copy_Tree
(Lhs
),
2440 Selector_Name
=> Make_Identifier
(Loc
, Chars
(Expr
))));
2443 end Rewrite_Discriminant
;
2449 function Replace_Type
(Expr
: Node_Id
) return Traverse_Result
is
2451 -- Note regarding the Root_Type test below: Aggregate components for
2452 -- self-referential types include attribute references to the current
2453 -- instance, of the form: Typ'access, etc.. These references are
2454 -- rewritten as references to the target of the aggregate: the
2455 -- left-hand side of an assignment, the entity in a declaration,
2456 -- or a temporary. Without this test, we would improperly extended
2457 -- this rewriting to attribute references whose prefix was not the
2458 -- type of the aggregate.
2460 if Nkind
(Expr
) = N_Attribute_Reference
2461 and then Is_Entity_Name
(Prefix
(Expr
))
2462 and then Is_Type
(Entity
(Prefix
(Expr
)))
2463 and then Root_Type
(Etype
(N
)) = Root_Type
(Entity
(Prefix
(Expr
)))
2465 if Is_Entity_Name
(Lhs
) then
2466 Rewrite
(Prefix
(Expr
),
2467 New_Occurrence_Of
(Entity
(Lhs
), Loc
));
2469 elsif Nkind
(Lhs
) = N_Selected_Component
then
2471 Make_Attribute_Reference
(Loc
,
2472 Attribute_Name
=> Name_Unrestricted_Access
,
2473 Prefix
=> New_Copy_Tree
(Prefix
(Lhs
))));
2474 Set_Analyzed
(Parent
(Expr
), False);
2478 Make_Attribute_Reference
(Loc
,
2479 Attribute_Name
=> Name_Unrestricted_Access
,
2480 Prefix
=> New_Copy_Tree
(Lhs
)));
2481 Set_Analyzed
(Parent
(Expr
), False);
2488 procedure Replace_Self_Reference
is
2489 new Traverse_Proc
(Replace_Type
);
2491 procedure Replace_Discriminants
is
2492 new Traverse_Proc
(Rewrite_Discriminant
);
2494 -- Start of processing for Build_Record_Aggr_Code
2497 if Has_Self_Reference
(N
) then
2498 Replace_Self_Reference
(N
);
2501 -- If the target of the aggregate is class-wide, we must convert it
2502 -- to the actual type of the aggregate, so that the proper components
2503 -- are visible. We know already that the types are compatible.
2505 if Present
(Etype
(Lhs
))
2506 and then Is_Class_Wide_Type
(Etype
(Lhs
))
2508 Target
:= Unchecked_Convert_To
(Typ
, Lhs
);
2513 -- Deal with the ancestor part of extension aggregates or with the
2514 -- discriminants of the root type.
2516 if Nkind
(N
) = N_Extension_Aggregate
then
2518 A
: constant Node_Id
:= Ancestor_Part
(N
);
2522 -- If the ancestor part is a subtype mark "T", we generate
2524 -- init-proc (T(tmp)); if T is constrained and
2525 -- init-proc (S(tmp)); where S applies an appropriate
2526 -- constraint if T is unconstrained
2528 if Is_Entity_Name
(A
) and then Is_Type
(Entity
(A
)) then
2529 Ancestor_Is_Subtype_Mark
:= True;
2531 if Is_Constrained
(Entity
(A
)) then
2532 Init_Typ
:= Entity
(A
);
2534 -- For an ancestor part given by an unconstrained type mark,
2535 -- create a subtype constrained by appropriate corresponding
2536 -- discriminant values coming from either associations of the
2537 -- aggregate or a constraint on a parent type. The subtype will
2538 -- be used to generate the correct default value for the
2541 elsif Has_Discriminants
(Entity
(A
)) then
2543 Anc_Typ
: constant Entity_Id
:= Entity
(A
);
2544 Anc_Constr
: constant List_Id
:= New_List
;
2545 Discrim
: Entity_Id
;
2546 Disc_Value
: Node_Id
;
2547 New_Indic
: Node_Id
;
2548 Subt_Decl
: Node_Id
;
2551 Discrim
:= First_Discriminant
(Anc_Typ
);
2552 while Present
(Discrim
) loop
2553 Disc_Value
:= Ancestor_Discriminant_Value
(Discrim
);
2554 Append_To
(Anc_Constr
, Disc_Value
);
2555 Next_Discriminant
(Discrim
);
2559 Make_Subtype_Indication
(Loc
,
2560 Subtype_Mark
=> New_Occurrence_Of
(Anc_Typ
, Loc
),
2562 Make_Index_Or_Discriminant_Constraint
(Loc
,
2563 Constraints
=> Anc_Constr
));
2565 Init_Typ
:= Create_Itype
(Ekind
(Anc_Typ
), N
);
2568 Make_Subtype_Declaration
(Loc
,
2569 Defining_Identifier
=> Init_Typ
,
2570 Subtype_Indication
=> New_Indic
);
2572 -- Itypes must be analyzed with checks off Declaration
2573 -- must have a parent for proper handling of subsidiary
2576 Set_Parent
(Subt_Decl
, N
);
2577 Analyze
(Subt_Decl
, Suppress
=> All_Checks
);
2581 Ref
:= Convert_To
(Init_Typ
, New_Copy_Tree
(Target
));
2582 Set_Assignment_OK
(Ref
);
2584 if not Is_Interface
(Init_Typ
) then
2586 Build_Initialization_Call
(Loc
,
2589 In_Init_Proc
=> Within_Init_Proc
,
2590 With_Default_Init
=> Has_Default_Init_Comps
(N
)
2592 Has_Task
(Base_Type
(Init_Typ
))));
2594 if Is_Constrained
(Entity
(A
))
2595 and then Has_Discriminants
(Entity
(A
))
2597 Check_Ancestor_Discriminants
(Entity
(A
));
2601 -- Handle calls to C++ constructors
2603 elsif Is_CPP_Constructor_Call
(A
) then
2604 Init_Typ
:= Etype
(A
);
2605 Ref
:= Convert_To
(Init_Typ
, New_Copy_Tree
(Target
));
2606 Set_Assignment_OK
(Ref
);
2609 Build_Initialization_Call
(Loc
,
2612 In_Init_Proc
=> Within_Init_Proc
,
2613 With_Default_Init
=> Has_Default_Init_Comps
(N
),
2614 Constructor_Ref
=> A
));
2616 -- Ada 2005 (AI-287): If the ancestor part is an aggregate of
2617 -- limited type, a recursive call expands the ancestor. Note that
2618 -- in the limited case, the ancestor part must be either a
2619 -- function call (possibly qualified, or wrapped in an unchecked
2620 -- conversion) or aggregate (definitely qualified).
2621 -- The ancestor part can also be a function call (that may be
2622 -- transformed into an explicit dereference) or a qualification
2625 elsif Is_Limited_Type
(Etype
(A
))
2626 and then Nkind_In
(Unqualify
(A
), N_Aggregate
,
2627 N_Extension_Aggregate
)
2629 Ancestor_Is_Expression
:= True;
2631 -- Set up finalization data for enclosing record, because
2632 -- controlled subcomponents of the ancestor part will be
2635 Gen_Ctrl_Actions_For_Aggr
;
2638 Build_Record_Aggr_Code
(
2640 Typ
=> Etype
(Unqualify
(A
)),
2644 Is_Limited_Ancestor_Expansion
=> True));
2646 -- If the ancestor part is an expression "E", we generate
2650 -- In Ada 2005, this includes the case of a (possibly qualified)
2651 -- limited function call. The assignment will turn into a
2652 -- build-in-place function call (for further details, see
2653 -- Make_Build_In_Place_Call_In_Assignment).
2656 Ancestor_Is_Expression
:= True;
2657 Init_Typ
:= Etype
(A
);
2659 -- If the ancestor part is an aggregate, force its full
2660 -- expansion, which was delayed.
2662 if Nkind_In
(Unqualify
(A
), N_Aggregate
,
2663 N_Extension_Aggregate
)
2665 Set_Analyzed
(A
, False);
2666 Set_Analyzed
(Expression
(A
), False);
2669 Ref
:= Convert_To
(Init_Typ
, New_Copy_Tree
(Target
));
2670 Set_Assignment_OK
(Ref
);
2672 -- Make the assignment without usual controlled actions since
2673 -- we only want the post adjust but not the pre finalize here
2674 -- Add manual adjust when necessary.
2676 Assign
:= New_List
(
2677 Make_OK_Assignment_Statement
(Loc
,
2680 Set_No_Ctrl_Actions
(First
(Assign
));
2682 -- Assign the tag now to make sure that the dispatching call in
2683 -- the subsequent deep_adjust works properly (unless VM_Target,
2684 -- where tags are implicit).
2686 if Tagged_Type_Expansion
then
2688 Make_OK_Assignment_Statement
(Loc
,
2690 Make_Selected_Component
(Loc
,
2691 Prefix
=> New_Copy_Tree
(Target
),
2694 (First_Tag_Component
(Base_Type
(Typ
)), Loc
)),
2697 Unchecked_Convert_To
(RTE
(RE_Tag
),
2700 (Access_Disp_Table
(Base_Type
(Typ
)))),
2703 Set_Assignment_OK
(Name
(Instr
));
2704 Append_To
(Assign
, Instr
);
2706 -- Ada 2005 (AI-251): If tagged type has progenitors we must
2707 -- also initialize tags of the secondary dispatch tables.
2709 if Has_Interfaces
(Base_Type
(Typ
)) then
2711 (Typ
=> Base_Type
(Typ
),
2713 Stmts_List
=> Assign
);
2717 -- Call Adjust manually
2719 if Needs_Finalization
(Etype
(A
))
2720 and then not Is_Limited_Type
(Etype
(A
))
2722 Append_List_To
(Assign
,
2724 Ref
=> New_Copy_Tree
(Ref
),
2726 Flist_Ref
=> New_Reference_To
(
2727 RTE
(RE_Global_Final_List
), Loc
),
2728 With_Attach
=> Make_Integer_Literal
(Loc
, 0)));
2732 Make_Unsuppress_Block
(Loc
, Name_Discriminant_Check
, Assign
));
2734 if Has_Discriminants
(Init_Typ
) then
2735 Check_Ancestor_Discriminants
(Init_Typ
);
2740 -- Normal case (not an extension aggregate)
2743 -- Generate the discriminant expressions, component by component.
2744 -- If the base type is an unchecked union, the discriminants are
2745 -- unknown to the back-end and absent from a value of the type, so
2746 -- assignments for them are not emitted.
2748 if Has_Discriminants
(Typ
)
2749 and then not Is_Unchecked_Union
(Base_Type
(Typ
))
2751 -- If the type is derived, and constrains discriminants of the
2752 -- parent type, these discriminants are not components of the
2753 -- aggregate, and must be initialized explicitly. They are not
2754 -- visible components of the object, but can become visible with
2755 -- a view conversion to the ancestor.
2759 Parent_Type
: Entity_Id
;
2761 Discr_Val
: Elmt_Id
;
2764 Btype
:= Base_Type
(Typ
);
2765 while Is_Derived_Type
(Btype
)
2766 and then Present
(Stored_Constraint
(Btype
))
2768 Parent_Type
:= Etype
(Btype
);
2770 Disc
:= First_Discriminant
(Parent_Type
);
2772 First_Elmt
(Stored_Constraint
(Base_Type
(Typ
)));
2773 while Present
(Discr_Val
) loop
2775 -- Only those discriminants of the parent that are not
2776 -- renamed by discriminants of the derived type need to
2777 -- be added explicitly.
2779 if not Is_Entity_Name
(Node
(Discr_Val
))
2781 Ekind
(Entity
(Node
(Discr_Val
))) /= E_Discriminant
2784 Make_Selected_Component
(Loc
,
2785 Prefix
=> New_Copy_Tree
(Target
),
2786 Selector_Name
=> New_Occurrence_Of
(Disc
, Loc
));
2789 Make_OK_Assignment_Statement
(Loc
,
2791 Expression
=> New_Copy_Tree
(Node
(Discr_Val
)));
2793 Set_No_Ctrl_Actions
(Instr
);
2794 Append_To
(L
, Instr
);
2797 Next_Discriminant
(Disc
);
2798 Next_Elmt
(Discr_Val
);
2801 Btype
:= Base_Type
(Parent_Type
);
2805 -- Generate discriminant init values for the visible discriminants
2808 Discriminant
: Entity_Id
;
2809 Discriminant_Value
: Node_Id
;
2812 Discriminant
:= First_Stored_Discriminant
(Typ
);
2813 while Present
(Discriminant
) loop
2815 Make_Selected_Component
(Loc
,
2816 Prefix
=> New_Copy_Tree
(Target
),
2817 Selector_Name
=> New_Occurrence_Of
(Discriminant
, Loc
));
2819 Discriminant_Value
:=
2820 Get_Discriminant_Value
(
2823 Discriminant_Constraint
(N_Typ
));
2826 Make_OK_Assignment_Statement
(Loc
,
2828 Expression
=> New_Copy_Tree
(Discriminant_Value
));
2830 Set_No_Ctrl_Actions
(Instr
);
2831 Append_To
(L
, Instr
);
2833 Next_Stored_Discriminant
(Discriminant
);
2839 -- For CPP types we generate an implicit call to the C++ default
2840 -- constructor to ensure the proper initialization of the _Tag
2843 if Is_CPP_Class
(Typ
) then
2844 pragma Assert
(Present
(Base_Init_Proc
(Typ
)));
2846 Build_Initialization_Call
(Loc
,
2851 -- Generate the assignments, component by component
2853 -- tmp.comp1 := Expr1_From_Aggr;
2854 -- tmp.comp2 := Expr2_From_Aggr;
2857 Comp
:= First
(Component_Associations
(N
));
2858 while Present
(Comp
) loop
2859 Selector
:= Entity
(First
(Choices
(Comp
)));
2863 if Is_CPP_Constructor_Call
(Expression
(Comp
)) then
2865 Build_Initialization_Call
(Loc
,
2866 Id_Ref
=> Make_Selected_Component
(Loc
,
2867 Prefix
=> New_Copy_Tree
(Target
),
2869 New_Occurrence_Of
(Selector
, Loc
)),
2870 Typ
=> Etype
(Selector
),
2872 With_Default_Init
=> True,
2873 Constructor_Ref
=> Expression
(Comp
)));
2875 -- Ada 2005 (AI-287): For each default-initialized component generate
2876 -- a call to the corresponding IP subprogram if available.
2878 elsif Box_Present
(Comp
)
2879 and then Has_Non_Null_Base_Init_Proc
(Etype
(Selector
))
2881 if Ekind
(Selector
) /= E_Discriminant
then
2882 Gen_Ctrl_Actions_For_Aggr
;
2885 -- Ada 2005 (AI-287): If the component type has tasks then
2886 -- generate the activation chain and master entities (except
2887 -- in case of an allocator because in that case these entities
2888 -- are generated by Build_Task_Allocate_Block_With_Init_Stmts).
2891 Ctype
: constant Entity_Id
:= Etype
(Selector
);
2892 Inside_Allocator
: Boolean := False;
2893 P
: Node_Id
:= Parent
(N
);
2896 if Is_Task_Type
(Ctype
) or else Has_Task
(Ctype
) then
2897 while Present
(P
) loop
2898 if Nkind
(P
) = N_Allocator
then
2899 Inside_Allocator
:= True;
2906 if not Inside_Init_Proc
and not Inside_Allocator
then
2907 Build_Activation_Chain_Entity
(N
);
2913 Build_Initialization_Call
(Loc
,
2914 Id_Ref
=> Make_Selected_Component
(Loc
,
2915 Prefix
=> New_Copy_Tree
(Target
),
2917 New_Occurrence_Of
(Selector
, Loc
)),
2918 Typ
=> Etype
(Selector
),
2920 With_Default_Init
=> True));
2922 -- Prepare for component assignment
2924 elsif Ekind
(Selector
) /= E_Discriminant
2925 or else Nkind
(N
) = N_Extension_Aggregate
2927 -- All the discriminants have now been assigned
2929 -- This is now a good moment to initialize and attach all the
2930 -- controllers. Their position may depend on the discriminants.
2932 if Ekind
(Selector
) /= E_Discriminant
then
2933 Gen_Ctrl_Actions_For_Aggr
;
2936 Comp_Type
:= Etype
(Selector
);
2938 Make_Selected_Component
(Loc
,
2939 Prefix
=> New_Copy_Tree
(Target
),
2940 Selector_Name
=> New_Occurrence_Of
(Selector
, Loc
));
2942 if Nkind
(Expression
(Comp
)) = N_Qualified_Expression
then
2943 Expr_Q
:= Expression
(Expression
(Comp
));
2945 Expr_Q
:= Expression
(Comp
);
2948 -- The controller is the one of the parent type defining the
2949 -- component (in case of inherited components).
2951 if Needs_Finalization
(Comp_Type
) then
2952 Internal_Final_List
:=
2953 Make_Selected_Component
(Loc
,
2954 Prefix
=> Convert_To
(
2955 Scope
(Original_Record_Component
(Selector
)),
2956 New_Copy_Tree
(Target
)),
2958 Make_Identifier
(Loc
, Name_uController
));
2960 Internal_Final_List
:=
2961 Make_Selected_Component
(Loc
,
2962 Prefix
=> Internal_Final_List
,
2963 Selector_Name
=> Make_Identifier
(Loc
, Name_F
));
2965 -- The internal final list can be part of a constant object
2967 Set_Assignment_OK
(Internal_Final_List
);
2970 Internal_Final_List
:= Empty
;
2973 -- Now either create the assignment or generate the code for the
2974 -- inner aggregate top-down.
2976 if Is_Delayed_Aggregate
(Expr_Q
) then
2978 -- We have the following case of aggregate nesting inside
2979 -- an object declaration:
2981 -- type Arr_Typ is array (Integer range <>) of ...;
2983 -- type Rec_Typ (...) is record
2984 -- Obj_Arr_Typ : Arr_Typ (A .. B);
2987 -- Obj_Rec_Typ : Rec_Typ := (...,
2988 -- Obj_Arr_Typ => (X => (...), Y => (...)));
2990 -- The length of the ranges of the aggregate and Obj_Add_Typ
2991 -- are equal (B - A = Y - X), but they do not coincide (X /=
2992 -- A and B /= Y). This case requires array sliding which is
2993 -- performed in the following manner:
2995 -- subtype Arr_Sub is Arr_Typ (X .. Y);
2997 -- Temp (X) := (...);
2999 -- Temp (Y) := (...);
3000 -- Obj_Rec_Typ.Obj_Arr_Typ := Temp;
3002 if Ekind
(Comp_Type
) = E_Array_Subtype
3003 and then Is_Int_Range_Bounds
(Aggregate_Bounds
(Expr_Q
))
3004 and then Is_Int_Range_Bounds
(First_Index
(Comp_Type
))
3006 Compatible_Int_Bounds
3007 (Agg_Bounds
=> Aggregate_Bounds
(Expr_Q
),
3008 Typ_Bounds
=> First_Index
(Comp_Type
))
3010 -- Create the array subtype with bounds equal to those of
3011 -- the corresponding aggregate.
3014 SubE
: constant Entity_Id
:= Make_Temporary
(Loc
, 'T');
3016 SubD
: constant Node_Id
:=
3017 Make_Subtype_Declaration
(Loc
,
3018 Defining_Identifier
=> SubE
,
3019 Subtype_Indication
=>
3020 Make_Subtype_Indication
(Loc
,
3023 (Etype
(Comp_Type
), Loc
),
3025 Make_Index_Or_Discriminant_Constraint
3027 Constraints
=> New_List
(
3029 (Aggregate_Bounds
(Expr_Q
))))));
3031 -- Create a temporary array of the above subtype which
3032 -- will be used to capture the aggregate assignments.
3034 TmpE
: constant Entity_Id
:= Make_Temporary
(Loc
, 'A', N
);
3036 TmpD
: constant Node_Id
:=
3037 Make_Object_Declaration
(Loc
,
3038 Defining_Identifier
=> TmpE
,
3039 Object_Definition
=>
3040 New_Reference_To
(SubE
, Loc
));
3043 Set_No_Initialization
(TmpD
);
3044 Append_To
(L
, SubD
);
3045 Append_To
(L
, TmpD
);
3047 -- Expand aggregate into assignments to the temp array
3050 Late_Expansion
(Expr_Q
, Comp_Type
,
3051 New_Reference_To
(TmpE
, Loc
), Internal_Final_List
));
3056 Make_Assignment_Statement
(Loc
,
3057 Name
=> New_Copy_Tree
(Comp_Expr
),
3058 Expression
=> New_Reference_To
(TmpE
, Loc
)));
3060 -- Do not pass the original aggregate to Gigi as is,
3061 -- since it will potentially clobber the front or the end
3062 -- of the array. Setting the expression to empty is safe
3063 -- since all aggregates are expanded into assignments.
3065 if Present
(Obj
) then
3066 Set_Expression
(Parent
(Obj
), Empty
);
3070 -- Normal case (sliding not required)
3074 Late_Expansion
(Expr_Q
, Comp_Type
, Comp_Expr
,
3075 Internal_Final_List
));
3078 -- Expr_Q is not delayed aggregate
3081 if Has_Discriminants
(Typ
) then
3082 Replace_Discriminants
(Expr_Q
);
3086 Make_OK_Assignment_Statement
(Loc
,
3088 Expression
=> Expr_Q
);
3090 Set_No_Ctrl_Actions
(Instr
);
3091 Append_To
(L
, Instr
);
3093 -- Adjust the tag if tagged (because of possible view
3094 -- conversions), unless compiling for a VM where tags are
3097 -- tmp.comp._tag := comp_typ'tag;
3099 if Is_Tagged_Type
(Comp_Type
)
3100 and then Tagged_Type_Expansion
3103 Make_OK_Assignment_Statement
(Loc
,
3105 Make_Selected_Component
(Loc
,
3106 Prefix
=> New_Copy_Tree
(Comp_Expr
),
3109 (First_Tag_Component
(Comp_Type
), Loc
)),
3112 Unchecked_Convert_To
(RTE
(RE_Tag
),
3114 (Node
(First_Elmt
(Access_Disp_Table
(Comp_Type
))),
3117 Append_To
(L
, Instr
);
3120 -- Adjust and Attach the component to the proper controller
3122 -- Adjust (tmp.comp);
3123 -- Attach_To_Final_List (tmp.comp,
3124 -- comp_typ (tmp)._record_controller.f)
3126 if Needs_Finalization
(Comp_Type
)
3127 and then not Is_Limited_Type
(Comp_Type
)
3131 Ref
=> New_Copy_Tree
(Comp_Expr
),
3133 Flist_Ref
=> Internal_Final_List
,
3134 With_Attach
=> Make_Integer_Literal
(Loc
, 1)));
3140 elsif Ekind
(Selector
) = E_Discriminant
3141 and then Nkind
(N
) /= N_Extension_Aggregate
3142 and then Nkind
(Parent
(N
)) = N_Component_Association
3143 and then Is_Constrained
(Typ
)
3145 -- We must check that the discriminant value imposed by the
3146 -- context is the same as the value given in the subaggregate,
3147 -- because after the expansion into assignments there is no
3148 -- record on which to perform a regular discriminant check.
3155 D_Val
:= First_Elmt
(Discriminant_Constraint
(Typ
));
3156 Disc
:= First_Discriminant
(Typ
);
3157 while Chars
(Disc
) /= Chars
(Selector
) loop
3158 Next_Discriminant
(Disc
);
3162 pragma Assert
(Present
(D_Val
));
3164 -- This check cannot performed for components that are
3165 -- constrained by a current instance, because this is not a
3166 -- value that can be compared with the actual constraint.
3168 if Nkind
(Node
(D_Val
)) /= N_Attribute_Reference
3169 or else not Is_Entity_Name
(Prefix
(Node
(D_Val
)))
3170 or else not Is_Type
(Entity
(Prefix
(Node
(D_Val
))))
3173 Make_Raise_Constraint_Error
(Loc
,
3176 Left_Opnd
=> New_Copy_Tree
(Node
(D_Val
)),
3177 Right_Opnd
=> Expression
(Comp
)),
3178 Reason
=> CE_Discriminant_Check_Failed
));
3181 -- Find self-reference in previous discriminant assignment,
3182 -- and replace with proper expression.
3189 while Present
(Ass
) loop
3190 if Nkind
(Ass
) = N_Assignment_Statement
3191 and then Nkind
(Name
(Ass
)) = N_Selected_Component
3192 and then Chars
(Selector_Name
(Name
(Ass
))) =
3196 (Ass
, New_Copy_Tree
(Expression
(Comp
)));
3209 -- If the type is tagged, the tag needs to be initialized (unless
3210 -- compiling for the Java VM where tags are implicit). It is done
3211 -- late in the initialization process because in some cases, we call
3212 -- the init proc of an ancestor which will not leave out the right tag
3214 if Ancestor_Is_Expression
then
3217 -- For CPP types we generated a call to the C++ default constructor
3218 -- before the components have been initialized to ensure the proper
3219 -- initialization of the _Tag component (see above).
3221 elsif Is_CPP_Class
(Typ
) then
3224 elsif Is_Tagged_Type
(Typ
) and then Tagged_Type_Expansion
then
3226 Make_OK_Assignment_Statement
(Loc
,
3228 Make_Selected_Component
(Loc
,
3229 Prefix
=> New_Copy_Tree
(Target
),
3232 (First_Tag_Component
(Base_Type
(Typ
)), Loc
)),
3235 Unchecked_Convert_To
(RTE
(RE_Tag
),
3237 (Node
(First_Elmt
(Access_Disp_Table
(Base_Type
(Typ
)))),
3240 Append_To
(L
, Instr
);
3242 -- Ada 2005 (AI-251): If the tagged type has been derived from
3243 -- abstract interfaces we must also initialize the tags of the
3244 -- secondary dispatch tables.
3246 if Has_Interfaces
(Base_Type
(Typ
)) then
3248 (Typ
=> Base_Type
(Typ
),
3254 -- If the controllers have not been initialized yet (by lack of non-
3255 -- discriminant components), let's do it now.
3257 Gen_Ctrl_Actions_For_Aggr
;
3260 end Build_Record_Aggr_Code
;
3262 -------------------------------
3263 -- Convert_Aggr_In_Allocator --
3264 -------------------------------
3266 procedure Convert_Aggr_In_Allocator
3271 Loc
: constant Source_Ptr
:= Sloc
(Aggr
);
3272 Typ
: constant Entity_Id
:= Etype
(Aggr
);
3273 Temp
: constant Entity_Id
:= Defining_Identifier
(Decl
);
3275 Occ
: constant Node_Id
:=
3276 Unchecked_Convert_To
(Typ
,
3277 Make_Explicit_Dereference
(Loc
,
3278 New_Reference_To
(Temp
, Loc
)));
3280 Access_Type
: constant Entity_Id
:= Etype
(Temp
);
3284 -- If the allocator is for an access discriminant, there is no
3285 -- finalization list for the anonymous access type, and the eventual
3286 -- finalization of the object is handled through the coextension
3287 -- mechanism. If the enclosing object is not dynamically allocated,
3288 -- the access discriminant is itself placed on the stack. Otherwise,
3289 -- some other finalization list is used (see exp_ch4.adb).
3291 -- Decl has been inserted in the code ahead of the allocator, using
3292 -- Insert_Actions. We use Insert_Actions below as well, to ensure that
3293 -- subsequent insertions are done in the proper order. Using (for
3294 -- example) Insert_Actions_After to place the expanded aggregate
3295 -- immediately after Decl may lead to out-of-order references if the
3296 -- allocator has generated a finalization list, as when the designated
3297 -- object is controlled and there is an open transient scope.
3299 if Ekind
(Access_Type
) = E_Anonymous_Access_Type
3300 and then Nkind
(Associated_Node_For_Itype
(Access_Type
)) =
3301 N_Discriminant_Specification
3305 elsif Needs_Finalization
(Typ
) then
3306 Flist
:= Find_Final_List
(Access_Type
);
3308 -- Otherwise there are no controlled actions to be performed.
3314 if Is_Array_Type
(Typ
) then
3315 Convert_Array_Aggr_In_Allocator
(Decl
, Aggr
, Occ
);
3317 elsif Has_Default_Init_Comps
(Aggr
) then
3319 L
: constant List_Id
:= New_List
;
3320 Init_Stmts
: List_Id
;
3327 Associated_Final_Chain
(Base_Type
(Access_Type
)));
3329 -- ??? Dubious actual for Obj: expect 'the original object being
3332 if Has_Task
(Typ
) then
3333 Build_Task_Allocate_Block_With_Init_Stmts
(L
, Aggr
, Init_Stmts
);
3334 Insert_Actions
(Alloc
, L
);
3336 Insert_Actions
(Alloc
, Init_Stmts
);
3341 Insert_Actions
(Alloc
,
3343 (Aggr
, Typ
, Occ
, Flist
,
3344 Associated_Final_Chain
(Base_Type
(Access_Type
))));
3346 -- ??? Dubious actual for Obj: expect 'the original object being
3350 end Convert_Aggr_In_Allocator
;
3352 --------------------------------
3353 -- Convert_Aggr_In_Assignment --
3354 --------------------------------
3356 procedure Convert_Aggr_In_Assignment
(N
: Node_Id
) is
3357 Aggr
: Node_Id
:= Expression
(N
);
3358 Typ
: constant Entity_Id
:= Etype
(Aggr
);
3359 Occ
: constant Node_Id
:= New_Copy_Tree
(Name
(N
));
3362 if Nkind
(Aggr
) = N_Qualified_Expression
then
3363 Aggr
:= Expression
(Aggr
);
3366 Insert_Actions_After
(N
,
3369 Find_Final_List
(Typ
, New_Copy_Tree
(Occ
))));
3370 end Convert_Aggr_In_Assignment
;
3372 ---------------------------------
3373 -- Convert_Aggr_In_Object_Decl --
3374 ---------------------------------
3376 procedure Convert_Aggr_In_Object_Decl
(N
: Node_Id
) is
3377 Obj
: constant Entity_Id
:= Defining_Identifier
(N
);
3378 Aggr
: Node_Id
:= Expression
(N
);
3379 Loc
: constant Source_Ptr
:= Sloc
(Aggr
);
3380 Typ
: constant Entity_Id
:= Etype
(Aggr
);
3381 Occ
: constant Node_Id
:= New_Occurrence_Of
(Obj
, Loc
);
3383 function Discriminants_Ok
return Boolean;
3384 -- If the object type is constrained, the discriminants in the
3385 -- aggregate must be checked against the discriminants of the subtype.
3386 -- This cannot be done using Apply_Discriminant_Checks because after
3387 -- expansion there is no aggregate left to check.
3389 ----------------------
3390 -- Discriminants_Ok --
3391 ----------------------
3393 function Discriminants_Ok
return Boolean is
3394 Cond
: Node_Id
:= Empty
;
3403 D
:= First_Discriminant
(Typ
);
3404 Disc1
:= First_Elmt
(Discriminant_Constraint
(Typ
));
3405 Disc2
:= First_Elmt
(Discriminant_Constraint
(Etype
(Obj
)));
3406 while Present
(Disc1
) and then Present
(Disc2
) loop
3407 Val1
:= Node
(Disc1
);
3408 Val2
:= Node
(Disc2
);
3410 if not Is_OK_Static_Expression
(Val1
)
3411 or else not Is_OK_Static_Expression
(Val2
)
3413 Check
:= Make_Op_Ne
(Loc
,
3414 Left_Opnd
=> Duplicate_Subexpr
(Val1
),
3415 Right_Opnd
=> Duplicate_Subexpr
(Val2
));
3421 Cond
:= Make_Or_Else
(Loc
,
3423 Right_Opnd
=> Check
);
3426 elsif Expr_Value
(Val1
) /= Expr_Value
(Val2
) then
3427 Apply_Compile_Time_Constraint_Error
(Aggr
,
3428 Msg
=> "incorrect value for discriminant&?",
3429 Reason
=> CE_Discriminant_Check_Failed
,
3434 Next_Discriminant
(D
);
3439 -- If any discriminant constraint is non-static, emit a check
3441 if Present
(Cond
) then
3443 Make_Raise_Constraint_Error
(Loc
,
3445 Reason
=> CE_Discriminant_Check_Failed
));
3449 end Discriminants_Ok
;
3451 -- Start of processing for Convert_Aggr_In_Object_Decl
3454 Set_Assignment_OK
(Occ
);
3456 if Nkind
(Aggr
) = N_Qualified_Expression
then
3457 Aggr
:= Expression
(Aggr
);
3460 if Has_Discriminants
(Typ
)
3461 and then Typ
/= Etype
(Obj
)
3462 and then Is_Constrained
(Etype
(Obj
))
3463 and then not Discriminants_Ok
3468 -- If the context is an extended return statement, it has its own
3469 -- finalization machinery (i.e. works like a transient scope) and
3470 -- we do not want to create an additional one, because objects on
3471 -- the finalization list of the return must be moved to the caller's
3472 -- finalization list to complete the return.
3474 -- However, if the aggregate is limited, it is built in place, and the
3475 -- controlled components are not assigned to intermediate temporaries
3476 -- so there is no need for a transient scope in this case either.
3478 if Requires_Transient_Scope
(Typ
)
3479 and then Ekind
(Current_Scope
) /= E_Return_Statement
3480 and then not Is_Limited_Type
(Typ
)
3482 Establish_Transient_Scope
3485 Is_Controlled
(Typ
) or else Has_Controlled_Component
(Typ
));
3488 Insert_Actions_After
(N
, Late_Expansion
(Aggr
, Typ
, Occ
, Obj
=> Obj
));
3489 Set_No_Initialization
(N
);
3490 Initialize_Discriminants
(N
, Typ
);
3491 end Convert_Aggr_In_Object_Decl
;
3493 -------------------------------------
3494 -- Convert_Array_Aggr_In_Allocator --
3495 -------------------------------------
3497 procedure Convert_Array_Aggr_In_Allocator
3502 Aggr_Code
: List_Id
;
3503 Typ
: constant Entity_Id
:= Etype
(Aggr
);
3504 Ctyp
: constant Entity_Id
:= Component_Type
(Typ
);
3507 -- The target is an explicit dereference of the allocated object.
3508 -- Generate component assignments to it, as for an aggregate that
3509 -- appears on the right-hand side of an assignment statement.
3512 Build_Array_Aggr_Code
(Aggr
,
3514 Index
=> First_Index
(Typ
),
3516 Scalar_Comp
=> Is_Scalar_Type
(Ctyp
));
3518 Insert_Actions_After
(Decl
, Aggr_Code
);
3519 end Convert_Array_Aggr_In_Allocator
;
3521 ----------------------------
3522 -- Convert_To_Assignments --
3523 ----------------------------
3525 procedure Convert_To_Assignments
(N
: Node_Id
; Typ
: Entity_Id
) is
3526 Loc
: constant Source_Ptr
:= Sloc
(N
);
3531 Target_Expr
: Node_Id
;
3532 Parent_Kind
: Node_Kind
;
3533 Unc_Decl
: Boolean := False;
3534 Parent_Node
: Node_Id
;
3537 pragma Assert
(not Is_Static_Dispatch_Table_Aggregate
(N
));
3538 pragma Assert
(Is_Record_Type
(Typ
));
3540 Parent_Node
:= Parent
(N
);
3541 Parent_Kind
:= Nkind
(Parent_Node
);
3543 if Parent_Kind
= N_Qualified_Expression
then
3545 -- Check if we are in a unconstrained declaration because in this
3546 -- case the current delayed expansion mechanism doesn't work when
3547 -- the declared object size depend on the initializing expr.
3550 Parent_Node
:= Parent
(Parent_Node
);
3551 Parent_Kind
:= Nkind
(Parent_Node
);
3553 if Parent_Kind
= N_Object_Declaration
then
3555 not Is_Entity_Name
(Object_Definition
(Parent_Node
))
3556 or else Has_Discriminants
3557 (Entity
(Object_Definition
(Parent_Node
)))
3558 or else Is_Class_Wide_Type
3559 (Entity
(Object_Definition
(Parent_Node
)));
3564 -- Just set the Delay flag in the cases where the transformation will be
3565 -- done top down from above.
3569 -- Internal aggregate (transformed when expanding the parent)
3571 or else Parent_Kind
= N_Aggregate
3572 or else Parent_Kind
= N_Extension_Aggregate
3573 or else Parent_Kind
= N_Component_Association
3575 -- Allocator (see Convert_Aggr_In_Allocator)
3577 or else Parent_Kind
= N_Allocator
3579 -- Object declaration (see Convert_Aggr_In_Object_Decl)
3581 or else (Parent_Kind
= N_Object_Declaration
and then not Unc_Decl
)
3583 -- Safe assignment (see Convert_Aggr_Assignments). So far only the
3584 -- assignments in init procs are taken into account.
3586 or else (Parent_Kind
= N_Assignment_Statement
3587 and then Inside_Init_Proc
)
3589 -- (Ada 2005) An inherently limited type in a return statement,
3590 -- which will be handled in a build-in-place fashion, and may be
3591 -- rewritten as an extended return and have its own finalization
3592 -- machinery. In the case of a simple return, the aggregate needs
3593 -- to be delayed until the scope for the return statement has been
3594 -- created, so that any finalization chain will be associated with
3595 -- that scope. For extended returns, we delay expansion to avoid the
3596 -- creation of an unwanted transient scope that could result in
3597 -- premature finalization of the return object (which is built in
3598 -- in place within the caller's scope).
3601 (Is_Inherently_Limited_Type
(Typ
)
3603 (Nkind
(Parent
(Parent_Node
)) = N_Extended_Return_Statement
3604 or else Nkind
(Parent_Node
) = N_Simple_Return_Statement
))
3606 Set_Expansion_Delayed
(N
);
3610 if Requires_Transient_Scope
(Typ
) then
3611 Establish_Transient_Scope
3613 Is_Controlled
(Typ
) or else Has_Controlled_Component
(Typ
));
3616 -- If the aggregate is non-limited, create a temporary. If it is limited
3617 -- and the context is an assignment, this is a subaggregate for an
3618 -- enclosing aggregate being expanded. It must be built in place, so use
3619 -- the target of the current assignment.
3621 if Is_Limited_Type
(Typ
)
3622 and then Nkind
(Parent
(N
)) = N_Assignment_Statement
3624 Target_Expr
:= New_Copy_Tree
(Name
(Parent
(N
)));
3626 (Parent
(N
), Build_Record_Aggr_Code
(N
, Typ
, Target_Expr
));
3627 Rewrite
(Parent
(N
), Make_Null_Statement
(Loc
));
3630 Temp
:= Make_Temporary
(Loc
, 'A', N
);
3632 -- If the type inherits unknown discriminants, use the view with
3633 -- known discriminants if available.
3635 if Has_Unknown_Discriminants
(Typ
)
3636 and then Present
(Underlying_Record_View
(Typ
))
3638 T
:= Underlying_Record_View
(Typ
);
3644 Make_Object_Declaration
(Loc
,
3645 Defining_Identifier
=> Temp
,
3646 Object_Definition
=> New_Occurrence_Of
(T
, Loc
));
3648 Set_No_Initialization
(Instr
);
3649 Insert_Action
(N
, Instr
);
3650 Initialize_Discriminants
(Instr
, T
);
3651 Target_Expr
:= New_Occurrence_Of
(Temp
, Loc
);
3652 Insert_Actions
(N
, Build_Record_Aggr_Code
(N
, T
, Target_Expr
));
3653 Rewrite
(N
, New_Occurrence_Of
(Temp
, Loc
));
3654 Analyze_And_Resolve
(N
, T
);
3656 end Convert_To_Assignments
;
3658 ---------------------------
3659 -- Convert_To_Positional --
3660 ---------------------------
3662 procedure Convert_To_Positional
3664 Max_Others_Replicate
: Nat
:= 5;
3665 Handle_Bit_Packed
: Boolean := False)
3667 Typ
: constant Entity_Id
:= Etype
(N
);
3669 Static_Components
: Boolean := True;
3671 procedure Check_Static_Components
;
3672 -- Check whether all components of the aggregate are compile-time known
3673 -- values, and can be passed as is to the back-end without further
3679 Ixb
: Node_Id
) return Boolean;
3680 -- Convert the aggregate into a purely positional form if possible. On
3681 -- entry the bounds of all dimensions are known to be static, and the
3682 -- total number of components is safe enough to expand.
3684 function Is_Flat
(N
: Node_Id
; Dims
: Int
) return Boolean;
3685 -- Return True iff the array N is flat (which is not trivial in the case
3686 -- of multidimensionsl aggregates).
3688 -----------------------------
3689 -- Check_Static_Components --
3690 -----------------------------
3692 procedure Check_Static_Components
is
3696 Static_Components
:= True;
3698 if Nkind
(N
) = N_String_Literal
then
3701 elsif Present
(Expressions
(N
)) then
3702 Expr
:= First
(Expressions
(N
));
3703 while Present
(Expr
) loop
3704 if Nkind
(Expr
) /= N_Aggregate
3705 or else not Compile_Time_Known_Aggregate
(Expr
)
3706 or else Expansion_Delayed
(Expr
)
3708 Static_Components
:= False;
3716 if Nkind
(N
) = N_Aggregate
3717 and then Present
(Component_Associations
(N
))
3719 Expr
:= First
(Component_Associations
(N
));
3720 while Present
(Expr
) loop
3721 if Nkind
(Expression
(Expr
)) = N_Integer_Literal
then
3724 elsif Nkind
(Expression
(Expr
)) /= N_Aggregate
3726 not Compile_Time_Known_Aggregate
(Expression
(Expr
))
3727 or else Expansion_Delayed
(Expression
(Expr
))
3729 Static_Components
:= False;
3736 end Check_Static_Components
;
3745 Ixb
: Node_Id
) return Boolean
3747 Loc
: constant Source_Ptr
:= Sloc
(N
);
3748 Blo
: constant Node_Id
:= Type_Low_Bound
(Etype
(Ixb
));
3749 Lo
: constant Node_Id
:= Type_Low_Bound
(Etype
(Ix
));
3750 Hi
: constant Node_Id
:= Type_High_Bound
(Etype
(Ix
));
3755 if Nkind
(Original_Node
(N
)) = N_String_Literal
then
3759 if not Compile_Time_Known_Value
(Lo
)
3760 or else not Compile_Time_Known_Value
(Hi
)
3765 Lov
:= Expr_Value
(Lo
);
3766 Hiv
:= Expr_Value
(Hi
);
3769 or else not Compile_Time_Known_Value
(Blo
)
3774 -- Determine if set of alternatives is suitable for conversion and
3775 -- build an array containing the values in sequence.
3778 Vals
: array (UI_To_Int
(Lov
) .. UI_To_Int
(Hiv
))
3779 of Node_Id
:= (others => Empty
);
3780 -- The values in the aggregate sorted appropriately
3783 -- Same data as Vals in list form
3786 -- Used to validate Max_Others_Replicate limit
3789 Num
: Int
:= UI_To_Int
(Lov
);
3795 if Present
(Expressions
(N
)) then
3796 Elmt
:= First
(Expressions
(N
));
3797 while Present
(Elmt
) loop
3798 if Nkind
(Elmt
) = N_Aggregate
3799 and then Present
(Next_Index
(Ix
))
3801 not Flatten
(Elmt
, Next_Index
(Ix
), Next_Index
(Ixb
))
3806 Vals
(Num
) := Relocate_Node
(Elmt
);
3813 if No
(Component_Associations
(N
)) then
3817 Elmt
:= First
(Component_Associations
(N
));
3819 if Nkind
(Expression
(Elmt
)) = N_Aggregate
then
3820 if Present
(Next_Index
(Ix
))
3823 (Expression
(Elmt
), Next_Index
(Ix
), Next_Index
(Ixb
))
3829 Component_Loop
: while Present
(Elmt
) loop
3830 Choice
:= First
(Choices
(Elmt
));
3831 Choice_Loop
: while Present
(Choice
) loop
3833 -- If we have an others choice, fill in the missing elements
3834 -- subject to the limit established by Max_Others_Replicate.
3836 if Nkind
(Choice
) = N_Others_Choice
then
3839 for J
in Vals
'Range loop
3840 if No
(Vals
(J
)) then
3841 Vals
(J
) := New_Copy_Tree
(Expression
(Elmt
));
3842 Rep_Count
:= Rep_Count
+ 1;
3844 -- Check for maximum others replication. Note that
3845 -- we skip this test if either of the restrictions
3846 -- No_Elaboration_Code or No_Implicit_Loops is
3847 -- active, if this is a preelaborable unit or a
3848 -- predefined unit. This ensures that predefined
3849 -- units get the same level of constant folding in
3850 -- Ada 95 and Ada 05, where their categorization
3854 P
: constant Entity_Id
:=
3855 Cunit_Entity
(Current_Sem_Unit
);
3858 -- Check if duplication OK and if so continue
3861 if Restriction_Active
(No_Elaboration_Code
)
3862 or else Restriction_Active
(No_Implicit_Loops
)
3863 or else Is_Preelaborated
(P
)
3864 or else (Ekind
(P
) = E_Package_Body
3866 Is_Preelaborated
(Spec_Entity
(P
)))
3868 Is_Predefined_File_Name
3869 (Unit_File_Name
(Get_Source_Unit
(P
)))
3873 -- If duplication not OK, then we return False
3874 -- if the replication count is too high
3876 elsif Rep_Count
> Max_Others_Replicate
then
3879 -- Continue on if duplication not OK, but the
3880 -- replication count is not excessive.
3889 exit Component_Loop
;
3891 -- Case of a subtype mark
3893 elsif Nkind
(Choice
) = N_Identifier
3894 and then Is_Type
(Entity
(Choice
))
3896 Lo
:= Type_Low_Bound
(Etype
(Choice
));
3897 Hi
:= Type_High_Bound
(Etype
(Choice
));
3899 -- Case of subtype indication
3901 elsif Nkind
(Choice
) = N_Subtype_Indication
then
3902 Lo
:= Low_Bound
(Range_Expression
(Constraint
(Choice
)));
3903 Hi
:= High_Bound
(Range_Expression
(Constraint
(Choice
)));
3907 elsif Nkind
(Choice
) = N_Range
then
3908 Lo
:= Low_Bound
(Choice
);
3909 Hi
:= High_Bound
(Choice
);
3911 -- Normal subexpression case
3913 else pragma Assert
(Nkind
(Choice
) in N_Subexpr
);
3914 if not Compile_Time_Known_Value
(Choice
) then
3918 Choice_Index
:= UI_To_Int
(Expr_Value
(Choice
));
3919 if Choice_Index
in Vals
'Range then
3920 Vals
(Choice_Index
) :=
3921 New_Copy_Tree
(Expression
(Elmt
));
3925 -- Choice is statically out-of-range, will be
3926 -- rewritten to raise Constraint_Error.
3933 -- Range cases merge with Lo,Hi set
3935 if not Compile_Time_Known_Value
(Lo
)
3937 not Compile_Time_Known_Value
(Hi
)
3941 for J
in UI_To_Int
(Expr_Value
(Lo
)) ..
3942 UI_To_Int
(Expr_Value
(Hi
))
3944 Vals
(J
) := New_Copy_Tree
(Expression
(Elmt
));
3950 end loop Choice_Loop
;
3953 end loop Component_Loop
;
3955 -- If we get here the conversion is possible
3958 for J
in Vals
'Range loop
3959 Append
(Vals
(J
), Vlist
);
3962 Rewrite
(N
, Make_Aggregate
(Loc
, Expressions
=> Vlist
));
3963 Set_Aggregate_Bounds
(N
, Aggregate_Bounds
(Original_Node
(N
)));
3972 function Is_Flat
(N
: Node_Id
; Dims
: Int
) return Boolean is
3979 elsif Nkind
(N
) = N_Aggregate
then
3980 if Present
(Component_Associations
(N
)) then
3984 Elmt
:= First
(Expressions
(N
));
3985 while Present
(Elmt
) loop
3986 if not Is_Flat
(Elmt
, Dims
- 1) then
4000 -- Start of processing for Convert_To_Positional
4003 -- Ada 2005 (AI-287): Do not convert in case of default initialized
4004 -- components because in this case will need to call the corresponding
4007 if Has_Default_Init_Comps
(N
) then
4011 if Is_Flat
(N
, Number_Dimensions
(Typ
)) then
4015 if Is_Bit_Packed_Array
(Typ
)
4016 and then not Handle_Bit_Packed
4021 -- Do not convert to positional if controlled components are involved
4022 -- since these require special processing
4024 if Has_Controlled_Component
(Typ
) then
4028 Check_Static_Components
;
4030 -- If the size is known, or all the components are static, try to
4031 -- build a fully positional aggregate.
4033 -- The size of the type may not be known for an aggregate with
4034 -- discriminated array components, but if the components are static
4035 -- it is still possible to verify statically that the length is
4036 -- compatible with the upper bound of the type, and therefore it is
4037 -- worth flattening such aggregates as well.
4039 -- For now the back-end expands these aggregates into individual
4040 -- assignments to the target anyway, but it is conceivable that
4041 -- it will eventually be able to treat such aggregates statically???
4043 if Aggr_Size_OK
(N
, Typ
)
4044 and then Flatten
(N
, First_Index
(Typ
), First_Index
(Base_Type
(Typ
)))
4046 if Static_Components
then
4047 Set_Compile_Time_Known_Aggregate
(N
);
4048 Set_Expansion_Delayed
(N
, False);
4051 Analyze_And_Resolve
(N
, Typ
);
4053 end Convert_To_Positional
;
4055 ----------------------------
4056 -- Expand_Array_Aggregate --
4057 ----------------------------
4059 -- Array aggregate expansion proceeds as follows:
4061 -- 1. If requested we generate code to perform all the array aggregate
4062 -- bound checks, specifically
4064 -- (a) Check that the index range defined by aggregate bounds is
4065 -- compatible with corresponding index subtype.
4067 -- (b) If an others choice is present check that no aggregate
4068 -- index is outside the bounds of the index constraint.
4070 -- (c) For multidimensional arrays make sure that all subaggregates
4071 -- corresponding to the same dimension have the same bounds.
4073 -- 2. Check for packed array aggregate which can be converted to a
4074 -- constant so that the aggregate disappeares completely.
4076 -- 3. Check case of nested aggregate. Generally nested aggregates are
4077 -- handled during the processing of the parent aggregate.
4079 -- 4. Check if the aggregate can be statically processed. If this is the
4080 -- case pass it as is to Gigi. Note that a necessary condition for
4081 -- static processing is that the aggregate be fully positional.
4083 -- 5. If in place aggregate expansion is possible (i.e. no need to create
4084 -- a temporary) then mark the aggregate as such and return. Otherwise
4085 -- create a new temporary and generate the appropriate initialization
4088 procedure Expand_Array_Aggregate
(N
: Node_Id
) is
4089 Loc
: constant Source_Ptr
:= Sloc
(N
);
4091 Typ
: constant Entity_Id
:= Etype
(N
);
4092 Ctyp
: constant Entity_Id
:= Component_Type
(Typ
);
4093 -- Typ is the correct constrained array subtype of the aggregate
4094 -- Ctyp is the corresponding component type.
4096 Aggr_Dimension
: constant Pos
:= Number_Dimensions
(Typ
);
4097 -- Number of aggregate index dimensions
4099 Aggr_Low
: array (1 .. Aggr_Dimension
) of Node_Id
;
4100 Aggr_High
: array (1 .. Aggr_Dimension
) of Node_Id
;
4101 -- Low and High bounds of the constraint for each aggregate index
4103 Aggr_Index_Typ
: array (1 .. Aggr_Dimension
) of Entity_Id
;
4104 -- The type of each index
4106 Maybe_In_Place_OK
: Boolean;
4107 -- If the type is neither controlled nor packed and the aggregate
4108 -- is the expression in an assignment, assignment in place may be
4109 -- possible, provided other conditions are met on the LHS.
4111 Others_Present
: array (1 .. Aggr_Dimension
) of Boolean :=
4113 -- If Others_Present (J) is True, then there is an others choice
4114 -- in one of the sub-aggregates of N at dimension J.
4116 procedure Build_Constrained_Type
(Positional
: Boolean);
4117 -- If the subtype is not static or unconstrained, build a constrained
4118 -- type using the computable sizes of the aggregate and its sub-
4121 procedure Check_Bounds
(Aggr_Bounds
: Node_Id
; Index_Bounds
: Node_Id
);
4122 -- Checks that the bounds of Aggr_Bounds are within the bounds defined
4125 procedure Check_Same_Aggr_Bounds
(Sub_Aggr
: Node_Id
; Dim
: Pos
);
4126 -- Checks that in a multi-dimensional array aggregate all subaggregates
4127 -- corresponding to the same dimension have the same bounds.
4128 -- Sub_Aggr is an array sub-aggregate. Dim is the dimension
4129 -- corresponding to the sub-aggregate.
4131 procedure Compute_Others_Present
(Sub_Aggr
: Node_Id
; Dim
: Pos
);
4132 -- Computes the values of array Others_Present. Sub_Aggr is the
4133 -- array sub-aggregate we start the computation from. Dim is the
4134 -- dimension corresponding to the sub-aggregate.
4136 function In_Place_Assign_OK
return Boolean;
4137 -- Simple predicate to determine whether an aggregate assignment can
4138 -- be done in place, because none of the new values can depend on the
4139 -- components of the target of the assignment.
4141 procedure Others_Check
(Sub_Aggr
: Node_Id
; Dim
: Pos
);
4142 -- Checks that if an others choice is present in any sub-aggregate no
4143 -- aggregate index is outside the bounds of the index constraint.
4144 -- Sub_Aggr is an array sub-aggregate. Dim is the dimension
4145 -- corresponding to the sub-aggregate.
4147 ----------------------------
4148 -- Build_Constrained_Type --
4149 ----------------------------
4151 procedure Build_Constrained_Type
(Positional
: Boolean) is
4152 Loc
: constant Source_Ptr
:= Sloc
(N
);
4153 Agg_Type
: constant Entity_Id
:= Make_Temporary
(Loc
, 'A');
4156 Typ
: constant Entity_Id
:= Etype
(N
);
4157 Indices
: constant List_Id
:= New_List
;
4162 -- If the aggregate is purely positional, all its subaggregates
4163 -- have the same size. We collect the dimensions from the first
4164 -- subaggregate at each level.
4169 for D
in 1 .. Number_Dimensions
(Typ
) loop
4170 Sub_Agg
:= First
(Expressions
(Sub_Agg
));
4174 while Present
(Comp
) loop
4181 Low_Bound
=> Make_Integer_Literal
(Loc
, 1),
4182 High_Bound
=> Make_Integer_Literal
(Loc
, Num
)));
4186 -- We know the aggregate type is unconstrained and the aggregate
4187 -- is not processable by the back end, therefore not necessarily
4188 -- positional. Retrieve each dimension bounds (computed earlier).
4190 for D
in 1 .. Number_Dimensions
(Typ
) loop
4193 Low_Bound
=> Aggr_Low
(D
),
4194 High_Bound
=> Aggr_High
(D
)),
4200 Make_Full_Type_Declaration
(Loc
,
4201 Defining_Identifier
=> Agg_Type
,
4203 Make_Constrained_Array_Definition
(Loc
,
4204 Discrete_Subtype_Definitions
=> Indices
,
4205 Component_Definition
=>
4206 Make_Component_Definition
(Loc
,
4207 Aliased_Present
=> False,
4208 Subtype_Indication
=>
4209 New_Occurrence_Of
(Component_Type
(Typ
), Loc
))));
4211 Insert_Action
(N
, Decl
);
4213 Set_Etype
(N
, Agg_Type
);
4214 Set_Is_Itype
(Agg_Type
);
4215 Freeze_Itype
(Agg_Type
, N
);
4216 end Build_Constrained_Type
;
4222 procedure Check_Bounds
(Aggr_Bounds
: Node_Id
; Index_Bounds
: Node_Id
) is
4229 Cond
: Node_Id
:= Empty
;
4232 Get_Index_Bounds
(Aggr_Bounds
, Aggr_Lo
, Aggr_Hi
);
4233 Get_Index_Bounds
(Index_Bounds
, Ind_Lo
, Ind_Hi
);
4235 -- Generate the following test:
4237 -- [constraint_error when
4238 -- Aggr_Lo <= Aggr_Hi and then
4239 -- (Aggr_Lo < Ind_Lo or else Aggr_Hi > Ind_Hi)]
4241 -- As an optimization try to see if some tests are trivially vacuous
4242 -- because we are comparing an expression against itself.
4244 if Aggr_Lo
= Ind_Lo
and then Aggr_Hi
= Ind_Hi
then
4247 elsif Aggr_Hi
= Ind_Hi
then
4250 Left_Opnd
=> Duplicate_Subexpr_Move_Checks
(Aggr_Lo
),
4251 Right_Opnd
=> Duplicate_Subexpr_Move_Checks
(Ind_Lo
));
4253 elsif Aggr_Lo
= Ind_Lo
then
4256 Left_Opnd
=> Duplicate_Subexpr_Move_Checks
(Aggr_Hi
),
4257 Right_Opnd
=> Duplicate_Subexpr_Move_Checks
(Ind_Hi
));
4264 Left_Opnd
=> Duplicate_Subexpr_Move_Checks
(Aggr_Lo
),
4265 Right_Opnd
=> Duplicate_Subexpr_Move_Checks
(Ind_Lo
)),
4269 Left_Opnd
=> Duplicate_Subexpr
(Aggr_Hi
),
4270 Right_Opnd
=> Duplicate_Subexpr
(Ind_Hi
)));
4273 if Present
(Cond
) then
4278 Left_Opnd
=> Duplicate_Subexpr_Move_Checks
(Aggr_Lo
),
4279 Right_Opnd
=> Duplicate_Subexpr_Move_Checks
(Aggr_Hi
)),
4281 Right_Opnd
=> Cond
);
4283 Set_Analyzed
(Left_Opnd
(Left_Opnd
(Cond
)), False);
4284 Set_Analyzed
(Right_Opnd
(Left_Opnd
(Cond
)), False);
4286 Make_Raise_Constraint_Error
(Loc
,
4288 Reason
=> CE_Length_Check_Failed
));
4292 ----------------------------
4293 -- Check_Same_Aggr_Bounds --
4294 ----------------------------
4296 procedure Check_Same_Aggr_Bounds
(Sub_Aggr
: Node_Id
; Dim
: Pos
) is
4297 Sub_Lo
: constant Node_Id
:= Low_Bound
(Aggregate_Bounds
(Sub_Aggr
));
4298 Sub_Hi
: constant Node_Id
:= High_Bound
(Aggregate_Bounds
(Sub_Aggr
));
4299 -- The bounds of this specific sub-aggregate
4301 Aggr_Lo
: constant Node_Id
:= Aggr_Low
(Dim
);
4302 Aggr_Hi
: constant Node_Id
:= Aggr_High
(Dim
);
4303 -- The bounds of the aggregate for this dimension
4305 Ind_Typ
: constant Entity_Id
:= Aggr_Index_Typ
(Dim
);
4306 -- The index type for this dimension.xxx
4308 Cond
: Node_Id
:= Empty
;
4313 -- If index checks are on generate the test
4315 -- [constraint_error when
4316 -- Aggr_Lo /= Sub_Lo or else Aggr_Hi /= Sub_Hi]
4318 -- As an optimization try to see if some tests are trivially vacuos
4319 -- because we are comparing an expression against itself. Also for
4320 -- the first dimension the test is trivially vacuous because there
4321 -- is just one aggregate for dimension 1.
4323 if Index_Checks_Suppressed
(Ind_Typ
) then
4327 or else (Aggr_Lo
= Sub_Lo
and then Aggr_Hi
= Sub_Hi
)
4331 elsif Aggr_Hi
= Sub_Hi
then
4334 Left_Opnd
=> Duplicate_Subexpr_Move_Checks
(Aggr_Lo
),
4335 Right_Opnd
=> Duplicate_Subexpr_Move_Checks
(Sub_Lo
));
4337 elsif Aggr_Lo
= Sub_Lo
then
4340 Left_Opnd
=> Duplicate_Subexpr_Move_Checks
(Aggr_Hi
),
4341 Right_Opnd
=> Duplicate_Subexpr_Move_Checks
(Sub_Hi
));
4348 Left_Opnd
=> Duplicate_Subexpr_Move_Checks
(Aggr_Lo
),
4349 Right_Opnd
=> Duplicate_Subexpr_Move_Checks
(Sub_Lo
)),
4353 Left_Opnd
=> Duplicate_Subexpr
(Aggr_Hi
),
4354 Right_Opnd
=> Duplicate_Subexpr
(Sub_Hi
)));
4357 if Present
(Cond
) then
4359 Make_Raise_Constraint_Error
(Loc
,
4361 Reason
=> CE_Length_Check_Failed
));
4364 -- Now look inside the sub-aggregate to see if there is more work
4366 if Dim
< Aggr_Dimension
then
4368 -- Process positional components
4370 if Present
(Expressions
(Sub_Aggr
)) then
4371 Expr
:= First
(Expressions
(Sub_Aggr
));
4372 while Present
(Expr
) loop
4373 Check_Same_Aggr_Bounds
(Expr
, Dim
+ 1);
4378 -- Process component associations
4380 if Present
(Component_Associations
(Sub_Aggr
)) then
4381 Assoc
:= First
(Component_Associations
(Sub_Aggr
));
4382 while Present
(Assoc
) loop
4383 Expr
:= Expression
(Assoc
);
4384 Check_Same_Aggr_Bounds
(Expr
, Dim
+ 1);
4389 end Check_Same_Aggr_Bounds
;
4391 ----------------------------
4392 -- Compute_Others_Present --
4393 ----------------------------
4395 procedure Compute_Others_Present
(Sub_Aggr
: Node_Id
; Dim
: Pos
) is
4400 if Present
(Component_Associations
(Sub_Aggr
)) then
4401 Assoc
:= Last
(Component_Associations
(Sub_Aggr
));
4403 if Nkind
(First
(Choices
(Assoc
))) = N_Others_Choice
then
4404 Others_Present
(Dim
) := True;
4408 -- Now look inside the sub-aggregate to see if there is more work
4410 if Dim
< Aggr_Dimension
then
4412 -- Process positional components
4414 if Present
(Expressions
(Sub_Aggr
)) then
4415 Expr
:= First
(Expressions
(Sub_Aggr
));
4416 while Present
(Expr
) loop
4417 Compute_Others_Present
(Expr
, Dim
+ 1);
4422 -- Process component associations
4424 if Present
(Component_Associations
(Sub_Aggr
)) then
4425 Assoc
:= First
(Component_Associations
(Sub_Aggr
));
4426 while Present
(Assoc
) loop
4427 Expr
:= Expression
(Assoc
);
4428 Compute_Others_Present
(Expr
, Dim
+ 1);
4433 end Compute_Others_Present
;
4435 ------------------------
4436 -- In_Place_Assign_OK --
4437 ------------------------
4439 function In_Place_Assign_OK
return Boolean is
4447 function Is_Others_Aggregate
(Aggr
: Node_Id
) return Boolean;
4448 -- Aggregates that consist of a single Others choice are safe
4449 -- if the single expression is.
4451 function Safe_Aggregate
(Aggr
: Node_Id
) return Boolean;
4452 -- Check recursively that each component of a (sub)aggregate does
4453 -- not depend on the variable being assigned to.
4455 function Safe_Component
(Expr
: Node_Id
) return Boolean;
4456 -- Verify that an expression cannot depend on the variable being
4457 -- assigned to. Room for improvement here (but less than before).
4459 -------------------------
4460 -- Is_Others_Aggregate --
4461 -------------------------
4463 function Is_Others_Aggregate
(Aggr
: Node_Id
) return Boolean is
4465 return No
(Expressions
(Aggr
))
4467 (First
(Choices
(First
(Component_Associations
(Aggr
)))))
4469 end Is_Others_Aggregate
;
4471 --------------------
4472 -- Safe_Aggregate --
4473 --------------------
4475 function Safe_Aggregate
(Aggr
: Node_Id
) return Boolean is
4479 if Present
(Expressions
(Aggr
)) then
4480 Expr
:= First
(Expressions
(Aggr
));
4481 while Present
(Expr
) loop
4482 if Nkind
(Expr
) = N_Aggregate
then
4483 if not Safe_Aggregate
(Expr
) then
4487 elsif not Safe_Component
(Expr
) then
4495 if Present
(Component_Associations
(Aggr
)) then
4496 Expr
:= First
(Component_Associations
(Aggr
));
4497 while Present
(Expr
) loop
4498 if Nkind
(Expression
(Expr
)) = N_Aggregate
then
4499 if not Safe_Aggregate
(Expression
(Expr
)) then
4503 elsif not Safe_Component
(Expression
(Expr
)) then
4514 --------------------
4515 -- Safe_Component --
4516 --------------------
4518 function Safe_Component
(Expr
: Node_Id
) return Boolean is
4519 Comp
: Node_Id
:= Expr
;
4521 function Check_Component
(Comp
: Node_Id
) return Boolean;
4522 -- Do the recursive traversal, after copy
4524 ---------------------
4525 -- Check_Component --
4526 ---------------------
4528 function Check_Component
(Comp
: Node_Id
) return Boolean is
4530 if Is_Overloaded
(Comp
) then
4534 return Compile_Time_Known_Value
(Comp
)
4536 or else (Is_Entity_Name
(Comp
)
4537 and then Present
(Entity
(Comp
))
4538 and then No
(Renamed_Object
(Entity
(Comp
))))
4540 or else (Nkind
(Comp
) = N_Attribute_Reference
4541 and then Check_Component
(Prefix
(Comp
)))
4543 or else (Nkind
(Comp
) in N_Binary_Op
4544 and then Check_Component
(Left_Opnd
(Comp
))
4545 and then Check_Component
(Right_Opnd
(Comp
)))
4547 or else (Nkind
(Comp
) in N_Unary_Op
4548 and then Check_Component
(Right_Opnd
(Comp
)))
4550 or else (Nkind
(Comp
) = N_Selected_Component
4551 and then Check_Component
(Prefix
(Comp
)))
4553 or else (Nkind
(Comp
) = N_Unchecked_Type_Conversion
4554 and then Check_Component
(Expression
(Comp
)));
4555 end Check_Component
;
4557 -- Start of processing for Safe_Component
4560 -- If the component appears in an association that may
4561 -- correspond to more than one element, it is not analyzed
4562 -- before the expansion into assignments, to avoid side effects.
4563 -- We analyze, but do not resolve the copy, to obtain sufficient
4564 -- entity information for the checks that follow. If component is
4565 -- overloaded we assume an unsafe function call.
4567 if not Analyzed
(Comp
) then
4568 if Is_Overloaded
(Expr
) then
4571 elsif Nkind
(Expr
) = N_Aggregate
4572 and then not Is_Others_Aggregate
(Expr
)
4576 elsif Nkind
(Expr
) = N_Allocator
then
4578 -- For now, too complex to analyze
4583 Comp
:= New_Copy_Tree
(Expr
);
4584 Set_Parent
(Comp
, Parent
(Expr
));
4588 if Nkind
(Comp
) = N_Aggregate
then
4589 return Safe_Aggregate
(Comp
);
4591 return Check_Component
(Comp
);
4595 -- Start of processing for In_Place_Assign_OK
4598 if Present
(Component_Associations
(N
)) then
4600 -- On assignment, sliding can take place, so we cannot do the
4601 -- assignment in place unless the bounds of the aggregate are
4602 -- statically equal to those of the target.
4604 -- If the aggregate is given by an others choice, the bounds
4605 -- are derived from the left-hand side, and the assignment is
4606 -- safe if the expression is.
4608 if Is_Others_Aggregate
(N
) then
4611 (Expression
(First
(Component_Associations
(N
))));
4614 Aggr_In
:= First_Index
(Etype
(N
));
4616 if Nkind
(Parent
(N
)) = N_Assignment_Statement
then
4617 Obj_In
:= First_Index
(Etype
(Name
(Parent
(N
))));
4620 -- Context is an allocator. Check bounds of aggregate
4621 -- against given type in qualified expression.
4623 pragma Assert
(Nkind
(Parent
(Parent
(N
))) = N_Allocator
);
4625 First_Index
(Etype
(Entity
(Subtype_Mark
(Parent
(N
)))));
4628 while Present
(Aggr_In
) loop
4629 Get_Index_Bounds
(Aggr_In
, Aggr_Lo
, Aggr_Hi
);
4630 Get_Index_Bounds
(Obj_In
, Obj_Lo
, Obj_Hi
);
4632 if not Compile_Time_Known_Value
(Aggr_Lo
)
4633 or else not Compile_Time_Known_Value
(Aggr_Hi
)
4634 or else not Compile_Time_Known_Value
(Obj_Lo
)
4635 or else not Compile_Time_Known_Value
(Obj_Hi
)
4636 or else Expr_Value
(Aggr_Lo
) /= Expr_Value
(Obj_Lo
)
4637 or else Expr_Value
(Aggr_Hi
) /= Expr_Value
(Obj_Hi
)
4642 Next_Index
(Aggr_In
);
4643 Next_Index
(Obj_In
);
4647 -- Now check the component values themselves
4649 return Safe_Aggregate
(N
);
4650 end In_Place_Assign_OK
;
4656 procedure Others_Check
(Sub_Aggr
: Node_Id
; Dim
: Pos
) is
4657 Aggr_Lo
: constant Node_Id
:= Aggr_Low
(Dim
);
4658 Aggr_Hi
: constant Node_Id
:= Aggr_High
(Dim
);
4659 -- The bounds of the aggregate for this dimension
4661 Ind_Typ
: constant Entity_Id
:= Aggr_Index_Typ
(Dim
);
4662 -- The index type for this dimension
4664 Need_To_Check
: Boolean := False;
4666 Choices_Lo
: Node_Id
:= Empty
;
4667 Choices_Hi
: Node_Id
:= Empty
;
4668 -- The lowest and highest discrete choices for a named sub-aggregate
4670 Nb_Choices
: Int
:= -1;
4671 -- The number of discrete non-others choices in this sub-aggregate
4673 Nb_Elements
: Uint
:= Uint_0
;
4674 -- The number of elements in a positional aggregate
4676 Cond
: Node_Id
:= Empty
;
4683 -- Check if we have an others choice. If we do make sure that this
4684 -- sub-aggregate contains at least one element in addition to the
4687 if Range_Checks_Suppressed
(Ind_Typ
) then
4688 Need_To_Check
:= False;
4690 elsif Present
(Expressions
(Sub_Aggr
))
4691 and then Present
(Component_Associations
(Sub_Aggr
))
4693 Need_To_Check
:= True;
4695 elsif Present
(Component_Associations
(Sub_Aggr
)) then
4696 Assoc
:= Last
(Component_Associations
(Sub_Aggr
));
4698 if Nkind
(First
(Choices
(Assoc
))) /= N_Others_Choice
then
4699 Need_To_Check
:= False;
4702 -- Count the number of discrete choices. Start with -1 because
4703 -- the others choice does not count.
4706 Assoc
:= First
(Component_Associations
(Sub_Aggr
));
4707 while Present
(Assoc
) loop
4708 Choice
:= First
(Choices
(Assoc
));
4709 while Present
(Choice
) loop
4710 Nb_Choices
:= Nb_Choices
+ 1;
4717 -- If there is only an others choice nothing to do
4719 Need_To_Check
:= (Nb_Choices
> 0);
4723 Need_To_Check
:= False;
4726 -- If we are dealing with a positional sub-aggregate with an others
4727 -- choice then compute the number or positional elements.
4729 if Need_To_Check
and then Present
(Expressions
(Sub_Aggr
)) then
4730 Expr
:= First
(Expressions
(Sub_Aggr
));
4731 Nb_Elements
:= Uint_0
;
4732 while Present
(Expr
) loop
4733 Nb_Elements
:= Nb_Elements
+ 1;
4737 -- If the aggregate contains discrete choices and an others choice
4738 -- compute the smallest and largest discrete choice values.
4740 elsif Need_To_Check
then
4741 Compute_Choices_Lo_And_Choices_Hi
: declare
4743 Table
: Case_Table_Type
(1 .. Nb_Choices
);
4744 -- Used to sort all the different choice values
4751 Assoc
:= First
(Component_Associations
(Sub_Aggr
));
4752 while Present
(Assoc
) loop
4753 Choice
:= First
(Choices
(Assoc
));
4754 while Present
(Choice
) loop
4755 if Nkind
(Choice
) = N_Others_Choice
then
4759 Get_Index_Bounds
(Choice
, Low
, High
);
4760 Table
(J
).Choice_Lo
:= Low
;
4761 Table
(J
).Choice_Hi
:= High
;
4770 -- Sort the discrete choices
4772 Sort_Case_Table
(Table
);
4774 Choices_Lo
:= Table
(1).Choice_Lo
;
4775 Choices_Hi
:= Table
(Nb_Choices
).Choice_Hi
;
4776 end Compute_Choices_Lo_And_Choices_Hi
;
4779 -- If no others choice in this sub-aggregate, or the aggregate
4780 -- comprises only an others choice, nothing to do.
4782 if not Need_To_Check
then
4785 -- If we are dealing with an aggregate containing an others choice
4786 -- and positional components, we generate the following test:
4788 -- if Ind_Typ'Pos (Aggr_Lo) + (Nb_Elements - 1) >
4789 -- Ind_Typ'Pos (Aggr_Hi)
4791 -- raise Constraint_Error;
4794 elsif Nb_Elements
> Uint_0
then
4800 Make_Attribute_Reference
(Loc
,
4801 Prefix
=> New_Reference_To
(Ind_Typ
, Loc
),
4802 Attribute_Name
=> Name_Pos
,
4805 (Duplicate_Subexpr_Move_Checks
(Aggr_Lo
))),
4806 Right_Opnd
=> Make_Integer_Literal
(Loc
, Nb_Elements
- 1)),
4809 Make_Attribute_Reference
(Loc
,
4810 Prefix
=> New_Reference_To
(Ind_Typ
, Loc
),
4811 Attribute_Name
=> Name_Pos
,
4812 Expressions
=> New_List
(
4813 Duplicate_Subexpr_Move_Checks
(Aggr_Hi
))));
4815 -- If we are dealing with an aggregate containing an others choice
4816 -- and discrete choices we generate the following test:
4818 -- [constraint_error when
4819 -- Choices_Lo < Aggr_Lo or else Choices_Hi > Aggr_Hi];
4827 Duplicate_Subexpr_Move_Checks
(Choices_Lo
),
4829 Duplicate_Subexpr_Move_Checks
(Aggr_Lo
)),
4834 Duplicate_Subexpr
(Choices_Hi
),
4836 Duplicate_Subexpr
(Aggr_Hi
)));
4839 if Present
(Cond
) then
4841 Make_Raise_Constraint_Error
(Loc
,
4843 Reason
=> CE_Length_Check_Failed
));
4844 -- Questionable reason code, shouldn't that be a
4845 -- CE_Range_Check_Failed ???
4848 -- Now look inside the sub-aggregate to see if there is more work
4850 if Dim
< Aggr_Dimension
then
4852 -- Process positional components
4854 if Present
(Expressions
(Sub_Aggr
)) then
4855 Expr
:= First
(Expressions
(Sub_Aggr
));
4856 while Present
(Expr
) loop
4857 Others_Check
(Expr
, Dim
+ 1);
4862 -- Process component associations
4864 if Present
(Component_Associations
(Sub_Aggr
)) then
4865 Assoc
:= First
(Component_Associations
(Sub_Aggr
));
4866 while Present
(Assoc
) loop
4867 Expr
:= Expression
(Assoc
);
4868 Others_Check
(Expr
, Dim
+ 1);
4875 -- Remaining Expand_Array_Aggregate variables
4878 -- Holds the temporary aggregate value
4881 -- Holds the declaration of Tmp
4883 Aggr_Code
: List_Id
;
4884 Parent_Node
: Node_Id
;
4885 Parent_Kind
: Node_Kind
;
4887 -- Start of processing for Expand_Array_Aggregate
4890 -- Do not touch the special aggregates of attributes used for Asm calls
4892 if Is_RTE
(Ctyp
, RE_Asm_Input_Operand
)
4893 or else Is_RTE
(Ctyp
, RE_Asm_Output_Operand
)
4898 -- If the semantic analyzer has determined that aggregate N will raise
4899 -- Constraint_Error at run-time, then the aggregate node has been
4900 -- replaced with an N_Raise_Constraint_Error node and we should
4903 pragma Assert
(not Raises_Constraint_Error
(N
));
4907 -- Check that the index range defined by aggregate bounds is
4908 -- compatible with corresponding index subtype.
4910 Index_Compatibility_Check
: declare
4911 Aggr_Index_Range
: Node_Id
:= First_Index
(Typ
);
4912 -- The current aggregate index range
4914 Index_Constraint
: Node_Id
:= First_Index
(Etype
(Typ
));
4915 -- The corresponding index constraint against which we have to
4916 -- check the above aggregate index range.
4919 Compute_Others_Present
(N
, 1);
4921 for J
in 1 .. Aggr_Dimension
loop
4922 -- There is no need to emit a check if an others choice is
4923 -- present for this array aggregate dimension since in this
4924 -- case one of N's sub-aggregates has taken its bounds from the
4925 -- context and these bounds must have been checked already. In
4926 -- addition all sub-aggregates corresponding to the same
4927 -- dimension must all have the same bounds (checked in (c) below).
4929 if not Range_Checks_Suppressed
(Etype
(Index_Constraint
))
4930 and then not Others_Present
(J
)
4932 -- We don't use Checks.Apply_Range_Check here because it emits
4933 -- a spurious check. Namely it checks that the range defined by
4934 -- the aggregate bounds is non empty. But we know this already
4937 Check_Bounds
(Aggr_Index_Range
, Index_Constraint
);
4940 -- Save the low and high bounds of the aggregate index as well as
4941 -- the index type for later use in checks (b) and (c) below.
4943 Aggr_Low
(J
) := Low_Bound
(Aggr_Index_Range
);
4944 Aggr_High
(J
) := High_Bound
(Aggr_Index_Range
);
4946 Aggr_Index_Typ
(J
) := Etype
(Index_Constraint
);
4948 Next_Index
(Aggr_Index_Range
);
4949 Next_Index
(Index_Constraint
);
4951 end Index_Compatibility_Check
;
4955 -- If an others choice is present check that no aggregate index is
4956 -- outside the bounds of the index constraint.
4958 Others_Check
(N
, 1);
4962 -- For multidimensional arrays make sure that all subaggregates
4963 -- corresponding to the same dimension have the same bounds.
4965 if Aggr_Dimension
> 1 then
4966 Check_Same_Aggr_Bounds
(N
, 1);
4971 -- Here we test for is packed array aggregate that we can handle at
4972 -- compile time. If so, return with transformation done. Note that we do
4973 -- this even if the aggregate is nested, because once we have done this
4974 -- processing, there is no more nested aggregate!
4976 if Packed_Array_Aggregate_Handled
(N
) then
4980 -- At this point we try to convert to positional form
4982 if Ekind
(Current_Scope
) = E_Package
4983 and then Static_Elaboration_Desired
(Current_Scope
)
4985 Convert_To_Positional
(N
, Max_Others_Replicate
=> 100);
4988 Convert_To_Positional
(N
);
4991 -- if the result is no longer an aggregate (e.g. it may be a string
4992 -- literal, or a temporary which has the needed value), then we are
4993 -- done, since there is no longer a nested aggregate.
4995 if Nkind
(N
) /= N_Aggregate
then
4998 -- We are also done if the result is an analyzed aggregate
4999 -- This case could use more comments ???
5002 and then N
/= Original_Node
(N
)
5007 -- If all aggregate components are compile-time known and the aggregate
5008 -- has been flattened, nothing left to do. The same occurs if the
5009 -- aggregate is used to initialize the components of an statically
5010 -- allocated dispatch table.
5012 if Compile_Time_Known_Aggregate
(N
)
5013 or else Is_Static_Dispatch_Table_Aggregate
(N
)
5015 Set_Expansion_Delayed
(N
, False);
5019 -- Now see if back end processing is possible
5021 if Backend_Processing_Possible
(N
) then
5023 -- If the aggregate is static but the constraints are not, build
5024 -- a static subtype for the aggregate, so that Gigi can place it
5025 -- in static memory. Perform an unchecked_conversion to the non-
5026 -- static type imposed by the context.
5029 Itype
: constant Entity_Id
:= Etype
(N
);
5031 Needs_Type
: Boolean := False;
5034 Index
:= First_Index
(Itype
);
5035 while Present
(Index
) loop
5036 if not Is_Static_Subtype
(Etype
(Index
)) then
5045 Build_Constrained_Type
(Positional
=> True);
5046 Rewrite
(N
, Unchecked_Convert_To
(Itype
, N
));
5056 -- Delay expansion for nested aggregates: it will be taken care of
5057 -- when the parent aggregate is expanded.
5059 Parent_Node
:= Parent
(N
);
5060 Parent_Kind
:= Nkind
(Parent_Node
);
5062 if Parent_Kind
= N_Qualified_Expression
then
5063 Parent_Node
:= Parent
(Parent_Node
);
5064 Parent_Kind
:= Nkind
(Parent_Node
);
5067 if Parent_Kind
= N_Aggregate
5068 or else Parent_Kind
= N_Extension_Aggregate
5069 or else Parent_Kind
= N_Component_Association
5070 or else (Parent_Kind
= N_Object_Declaration
5071 and then Needs_Finalization
(Typ
))
5072 or else (Parent_Kind
= N_Assignment_Statement
5073 and then Inside_Init_Proc
)
5075 if Static_Array_Aggregate
(N
)
5076 or else Compile_Time_Known_Aggregate
(N
)
5078 Set_Expansion_Delayed
(N
, False);
5081 Set_Expansion_Delayed
(N
);
5088 -- Look if in place aggregate expansion is possible
5090 -- For object declarations we build the aggregate in place, unless
5091 -- the array is bit-packed or the component is controlled.
5093 -- For assignments we do the assignment in place if all the component
5094 -- associations have compile-time known values. For other cases we
5095 -- create a temporary. The analysis for safety of on-line assignment
5096 -- is delicate, i.e. we don't know how to do it fully yet ???
5098 -- For allocators we assign to the designated object in place if the
5099 -- aggregate meets the same conditions as other in-place assignments.
5100 -- In this case the aggregate may not come from source but was created
5101 -- for default initialization, e.g. with Initialize_Scalars.
5103 if Requires_Transient_Scope
(Typ
) then
5104 Establish_Transient_Scope
5105 (N
, Sec_Stack
=> Has_Controlled_Component
(Typ
));
5108 if Has_Default_Init_Comps
(N
) then
5109 Maybe_In_Place_OK
:= False;
5111 elsif Is_Bit_Packed_Array
(Typ
)
5112 or else Has_Controlled_Component
(Typ
)
5114 Maybe_In_Place_OK
:= False;
5117 Maybe_In_Place_OK
:=
5118 (Nkind
(Parent
(N
)) = N_Assignment_Statement
5119 and then Comes_From_Source
(N
)
5120 and then In_Place_Assign_OK
)
5123 (Nkind
(Parent
(Parent
(N
))) = N_Allocator
5124 and then In_Place_Assign_OK
);
5127 -- If this is an array of tasks, it will be expanded into build-in-place
5128 -- assignments. Build an activation chain for the tasks now.
5130 if Has_Task
(Etype
(N
)) then
5131 Build_Activation_Chain_Entity
(N
);
5134 -- Should document these individual tests ???
5136 if not Has_Default_Init_Comps
(N
)
5137 and then Comes_From_Source
(Parent
(N
))
5138 and then Nkind
(Parent
(N
)) = N_Object_Declaration
5140 Must_Slide
(Etype
(Defining_Identifier
(Parent
(N
))), Typ
)
5141 and then N
= Expression
(Parent
(N
))
5142 and then not Is_Bit_Packed_Array
(Typ
)
5143 and then not Has_Controlled_Component
(Typ
)
5145 -- If the aggregate is the expression in an object declaration, it
5146 -- cannot be expanded in place. Lookahead in the current declarative
5147 -- part to find an address clause for the object being declared. If
5148 -- one is present, we cannot build in place. Unclear comment???
5150 and then not Has_Following_Address_Clause
(Parent
(N
))
5152 Tmp
:= Defining_Identifier
(Parent
(N
));
5153 Set_No_Initialization
(Parent
(N
));
5154 Set_Expression
(Parent
(N
), Empty
);
5156 -- Set the type of the entity, for use in the analysis of the
5157 -- subsequent indexed assignments. If the nominal type is not
5158 -- constrained, build a subtype from the known bounds of the
5159 -- aggregate. If the declaration has a subtype mark, use it,
5160 -- otherwise use the itype of the aggregate.
5162 if not Is_Constrained
(Typ
) then
5163 Build_Constrained_Type
(Positional
=> False);
5164 elsif Is_Entity_Name
(Object_Definition
(Parent
(N
)))
5165 and then Is_Constrained
(Entity
(Object_Definition
(Parent
(N
))))
5167 Set_Etype
(Tmp
, Entity
(Object_Definition
(Parent
(N
))));
5169 Set_Size_Known_At_Compile_Time
(Typ
, False);
5170 Set_Etype
(Tmp
, Typ
);
5173 elsif Maybe_In_Place_OK
5174 and then Nkind
(Parent
(N
)) = N_Qualified_Expression
5175 and then Nkind
(Parent
(Parent
(N
))) = N_Allocator
5177 Set_Expansion_Delayed
(N
);
5180 -- In the remaining cases the aggregate is the RHS of an assignment
5182 elsif Maybe_In_Place_OK
5183 and then Is_Entity_Name
(Name
(Parent
(N
)))
5185 Tmp
:= Entity
(Name
(Parent
(N
)));
5187 if Etype
(Tmp
) /= Etype
(N
) then
5188 Apply_Length_Check
(N
, Etype
(Tmp
));
5190 if Nkind
(N
) = N_Raise_Constraint_Error
then
5192 -- Static error, nothing further to expand
5198 elsif Maybe_In_Place_OK
5199 and then Nkind
(Name
(Parent
(N
))) = N_Explicit_Dereference
5200 and then Is_Entity_Name
(Prefix
(Name
(Parent
(N
))))
5202 Tmp
:= Name
(Parent
(N
));
5204 if Etype
(Tmp
) /= Etype
(N
) then
5205 Apply_Length_Check
(N
, Etype
(Tmp
));
5208 elsif Maybe_In_Place_OK
5209 and then Nkind
(Name
(Parent
(N
))) = N_Slice
5210 and then Safe_Slice_Assignment
(N
)
5212 -- Safe_Slice_Assignment rewrites assignment as a loop
5218 -- In place aggregate expansion is not possible
5221 Maybe_In_Place_OK
:= False;
5222 Tmp
:= Make_Temporary
(Loc
, 'A', N
);
5224 Make_Object_Declaration
5226 Defining_Identifier
=> Tmp
,
5227 Object_Definition
=> New_Occurrence_Of
(Typ
, Loc
));
5228 Set_No_Initialization
(Tmp_Decl
, True);
5230 -- If we are within a loop, the temporary will be pushed on the
5231 -- stack at each iteration. If the aggregate is the expression for an
5232 -- allocator, it will be immediately copied to the heap and can
5233 -- be reclaimed at once. We create a transient scope around the
5234 -- aggregate for this purpose.
5236 if Ekind
(Current_Scope
) = E_Loop
5237 and then Nkind
(Parent
(Parent
(N
))) = N_Allocator
5239 Establish_Transient_Scope
(N
, False);
5242 Insert_Action
(N
, Tmp_Decl
);
5245 -- Construct and insert the aggregate code. We can safely suppress index
5246 -- checks because this code is guaranteed not to raise CE on index
5247 -- checks. However we should *not* suppress all checks.
5253 if Nkind
(Tmp
) = N_Defining_Identifier
then
5254 Target
:= New_Reference_To
(Tmp
, Loc
);
5258 if Has_Default_Init_Comps
(N
) then
5260 -- Ada 2005 (AI-287): This case has not been analyzed???
5262 raise Program_Error
;
5265 -- Name in assignment is explicit dereference
5267 Target
:= New_Copy
(Tmp
);
5271 Build_Array_Aggr_Code
(N
,
5273 Index
=> First_Index
(Typ
),
5275 Scalar_Comp
=> Is_Scalar_Type
(Ctyp
));
5278 if Comes_From_Source
(Tmp
) then
5279 Insert_Actions_After
(Parent
(N
), Aggr_Code
);
5282 Insert_Actions
(N
, Aggr_Code
);
5285 -- If the aggregate has been assigned in place, remove the original
5288 if Nkind
(Parent
(N
)) = N_Assignment_Statement
5289 and then Maybe_In_Place_OK
5291 Rewrite
(Parent
(N
), Make_Null_Statement
(Loc
));
5293 elsif Nkind
(Parent
(N
)) /= N_Object_Declaration
5294 or else Tmp
/= Defining_Identifier
(Parent
(N
))
5296 Rewrite
(N
, New_Occurrence_Of
(Tmp
, Loc
));
5297 Analyze_And_Resolve
(N
, Typ
);
5299 end Expand_Array_Aggregate
;
5301 ------------------------
5302 -- Expand_N_Aggregate --
5303 ------------------------
5305 procedure Expand_N_Aggregate
(N
: Node_Id
) is
5307 if Is_Record_Type
(Etype
(N
)) then
5308 Expand_Record_Aggregate
(N
);
5310 Expand_Array_Aggregate
(N
);
5313 when RE_Not_Available
=>
5315 end Expand_N_Aggregate
;
5317 ----------------------------------
5318 -- Expand_N_Extension_Aggregate --
5319 ----------------------------------
5321 -- If the ancestor part is an expression, add a component association for
5322 -- the parent field. If the type of the ancestor part is not the direct
5323 -- parent of the expected type, build recursively the needed ancestors.
5324 -- If the ancestor part is a subtype_mark, replace aggregate with a decla-
5325 -- ration for a temporary of the expected type, followed by individual
5326 -- assignments to the given components.
5328 procedure Expand_N_Extension_Aggregate
(N
: Node_Id
) is
5329 Loc
: constant Source_Ptr
:= Sloc
(N
);
5330 A
: constant Node_Id
:= Ancestor_Part
(N
);
5331 Typ
: constant Entity_Id
:= Etype
(N
);
5334 -- If the ancestor is a subtype mark, an init proc must be called
5335 -- on the resulting object which thus has to be materialized in
5338 if Is_Entity_Name
(A
) and then Is_Type
(Entity
(A
)) then
5339 Convert_To_Assignments
(N
, Typ
);
5341 -- The extension aggregate is transformed into a record aggregate
5342 -- of the following form (c1 and c2 are inherited components)
5344 -- (Exp with c3 => a, c4 => b)
5345 -- ==> (c1 => Exp.c1, c2 => Exp.c2, c1 => a, c2 => b)
5350 if Tagged_Type_Expansion
then
5351 Expand_Record_Aggregate
(N
,
5354 (Node
(First_Elmt
(Access_Disp_Table
(Typ
))), Loc
),
5357 -- No tag is needed in the case of a VM
5358 Expand_Record_Aggregate
(N
,
5364 when RE_Not_Available
=>
5366 end Expand_N_Extension_Aggregate
;
5368 -----------------------------
5369 -- Expand_Record_Aggregate --
5370 -----------------------------
5372 procedure Expand_Record_Aggregate
5374 Orig_Tag
: Node_Id
:= Empty
;
5375 Parent_Expr
: Node_Id
:= Empty
)
5377 Loc
: constant Source_Ptr
:= Sloc
(N
);
5378 Comps
: constant List_Id
:= Component_Associations
(N
);
5379 Typ
: constant Entity_Id
:= Etype
(N
);
5380 Base_Typ
: constant Entity_Id
:= Base_Type
(Typ
);
5382 Static_Components
: Boolean := True;
5383 -- Flag to indicate whether all components are compile-time known,
5384 -- and the aggregate can be constructed statically and handled by
5387 function Component_Not_OK_For_Backend
return Boolean;
5388 -- Check for presence of component which makes it impossible for the
5389 -- backend to process the aggregate, thus requiring the use of a series
5390 -- of assignment statements. Cases checked for are a nested aggregate
5391 -- needing Late_Expansion, the presence of a tagged component which may
5392 -- need tag adjustment, and a bit unaligned component reference.
5394 -- We also force expansion into assignments if a component is of a
5395 -- mutable type (including a private type with discriminants) because
5396 -- in that case the size of the component to be copied may be smaller
5397 -- than the side of the target, and there is no simple way for gigi
5398 -- to compute the size of the object to be copied.
5400 -- NOTE: This is part of the ongoing work to define precisely the
5401 -- interface between front-end and back-end handling of aggregates.
5402 -- In general it is desirable to pass aggregates as they are to gigi,
5403 -- in order to minimize elaboration code. This is one case where the
5404 -- semantics of Ada complicate the analysis and lead to anomalies in
5405 -- the gcc back-end if the aggregate is not expanded into assignments.
5407 ----------------------------------
5408 -- Component_Not_OK_For_Backend --
5409 ----------------------------------
5411 function Component_Not_OK_For_Backend
return Boolean is
5421 while Present
(C
) loop
5422 if Nkind
(Expression
(C
)) = N_Qualified_Expression
then
5423 Expr_Q
:= Expression
(Expression
(C
));
5425 Expr_Q
:= Expression
(C
);
5428 -- Return true if the aggregate has any associations for tagged
5429 -- components that may require tag adjustment.
5431 -- These are cases where the source expression may have a tag that
5432 -- could differ from the component tag (e.g., can occur for type
5433 -- conversions and formal parameters). (Tag adjustment not needed
5434 -- if VM_Target because object tags are implicit in the machine.)
5436 if Is_Tagged_Type
(Etype
(Expr_Q
))
5437 and then (Nkind
(Expr_Q
) = N_Type_Conversion
5438 or else (Is_Entity_Name
(Expr_Q
)
5440 Ekind
(Entity
(Expr_Q
)) in Formal_Kind
))
5441 and then Tagged_Type_Expansion
5443 Static_Components
:= False;
5446 elsif Is_Delayed_Aggregate
(Expr_Q
) then
5447 Static_Components
:= False;
5450 elsif Possible_Bit_Aligned_Component
(Expr_Q
) then
5451 Static_Components
:= False;
5455 if Is_Scalar_Type
(Etype
(Expr_Q
)) then
5456 if not Compile_Time_Known_Value
(Expr_Q
) then
5457 Static_Components
:= False;
5460 elsif Nkind
(Expr_Q
) /= N_Aggregate
5461 or else not Compile_Time_Known_Aggregate
(Expr_Q
)
5463 Static_Components
:= False;
5465 if Is_Private_Type
(Etype
(Expr_Q
))
5466 and then Has_Discriminants
(Etype
(Expr_Q
))
5476 end Component_Not_OK_For_Backend
;
5478 -- Remaining Expand_Record_Aggregate variables
5480 Tag_Value
: Node_Id
;
5484 -- Start of processing for Expand_Record_Aggregate
5487 -- If the aggregate is to be assigned to an atomic variable, we
5488 -- have to prevent a piecemeal assignment even if the aggregate
5489 -- is to be expanded. We create a temporary for the aggregate, and
5490 -- assign the temporary instead, so that the back end can generate
5491 -- an atomic move for it.
5494 and then Comes_From_Source
(Parent
(N
))
5495 and then Is_Atomic_Aggregate
(N
, Typ
)
5499 -- No special management required for aggregates used to initialize
5500 -- statically allocated dispatch tables
5502 elsif Is_Static_Dispatch_Table_Aggregate
(N
) then
5506 -- Ada 2005 (AI-318-2): We need to convert to assignments if components
5507 -- are build-in-place function calls. This test could be more specific,
5508 -- but doing it for all inherently limited aggregates seems harmless.
5509 -- The assignments will turn into build-in-place function calls (see
5510 -- Make_Build_In_Place_Call_In_Assignment).
5512 if Ada_Version
>= Ada_05
and then Is_Inherently_Limited_Type
(Typ
) then
5513 Convert_To_Assignments
(N
, Typ
);
5515 -- Gigi doesn't handle properly temporaries of variable size
5516 -- so we generate it in the front-end
5518 elsif not Size_Known_At_Compile_Time
(Typ
) then
5519 Convert_To_Assignments
(N
, Typ
);
5521 -- Temporaries for controlled aggregates need to be attached to a
5522 -- final chain in order to be properly finalized, so it has to
5523 -- be created in the front-end
5525 elsif Is_Controlled
(Typ
)
5526 or else Has_Controlled_Component
(Base_Type
(Typ
))
5528 Convert_To_Assignments
(N
, Typ
);
5530 -- Ada 2005 (AI-287): In case of default initialized components we
5531 -- convert the aggregate into assignments.
5533 elsif Has_Default_Init_Comps
(N
) then
5534 Convert_To_Assignments
(N
, Typ
);
5538 elsif Component_Not_OK_For_Backend
then
5539 Convert_To_Assignments
(N
, Typ
);
5541 -- If an ancestor is private, some components are not inherited and
5542 -- we cannot expand into a record aggregate
5544 elsif Has_Private_Ancestor
(Typ
) then
5545 Convert_To_Assignments
(N
, Typ
);
5547 -- ??? The following was done to compile fxacc00.ads in the ACVCs. Gigi
5548 -- is not able to handle the aggregate for Late_Request.
5550 elsif Is_Tagged_Type
(Typ
) and then Has_Discriminants
(Typ
) then
5551 Convert_To_Assignments
(N
, Typ
);
5553 -- If the tagged types covers interface types we need to initialize all
5554 -- hidden components containing pointers to secondary dispatch tables.
5556 elsif Is_Tagged_Type
(Typ
) and then Has_Interfaces
(Typ
) then
5557 Convert_To_Assignments
(N
, Typ
);
5559 -- If some components are mutable, the size of the aggregate component
5560 -- may be distinct from the default size of the type component, so
5561 -- we need to expand to insure that the back-end copies the proper
5562 -- size of the data.
5564 elsif Has_Mutable_Components
(Typ
) then
5565 Convert_To_Assignments
(N
, Typ
);
5567 -- If the type involved has any non-bit aligned components, then we are
5568 -- not sure that the back end can handle this case correctly.
5570 elsif Type_May_Have_Bit_Aligned_Components
(Typ
) then
5571 Convert_To_Assignments
(N
, Typ
);
5573 -- In all other cases, build a proper aggregate handlable by gigi
5576 if Nkind
(N
) = N_Aggregate
then
5578 -- If the aggregate is static and can be handled by the back-end,
5579 -- nothing left to do.
5581 if Static_Components
then
5582 Set_Compile_Time_Known_Aggregate
(N
);
5583 Set_Expansion_Delayed
(N
, False);
5587 -- If no discriminants, nothing special to do
5589 if not Has_Discriminants
(Typ
) then
5592 -- Case of discriminants present
5594 elsif Is_Derived_Type
(Typ
) then
5596 -- For untagged types, non-stored discriminants are replaced
5597 -- with stored discriminants, which are the ones that gigi uses
5598 -- to describe the type and its components.
5600 Generate_Aggregate_For_Derived_Type
: declare
5601 Constraints
: constant List_Id
:= New_List
;
5602 First_Comp
: Node_Id
;
5603 Discriminant
: Entity_Id
;
5605 Num_Disc
: Int
:= 0;
5606 Num_Gird
: Int
:= 0;
5608 procedure Prepend_Stored_Values
(T
: Entity_Id
);
5609 -- Scan the list of stored discriminants of the type, and add
5610 -- their values to the aggregate being built.
5612 ---------------------------
5613 -- Prepend_Stored_Values --
5614 ---------------------------
5616 procedure Prepend_Stored_Values
(T
: Entity_Id
) is
5618 Discriminant
:= First_Stored_Discriminant
(T
);
5619 while Present
(Discriminant
) loop
5621 Make_Component_Association
(Loc
,
5623 New_List
(New_Occurrence_Of
(Discriminant
, Loc
)),
5627 Get_Discriminant_Value
(
5630 Discriminant_Constraint
(Typ
))));
5632 if No
(First_Comp
) then
5633 Prepend_To
(Component_Associations
(N
), New_Comp
);
5635 Insert_After
(First_Comp
, New_Comp
);
5638 First_Comp
:= New_Comp
;
5639 Next_Stored_Discriminant
(Discriminant
);
5641 end Prepend_Stored_Values
;
5643 -- Start of processing for Generate_Aggregate_For_Derived_Type
5646 -- Remove the associations for the discriminant of derived type
5648 First_Comp
:= First
(Component_Associations
(N
));
5649 while Present
(First_Comp
) loop
5654 (First
(Choices
(Comp
)))) = E_Discriminant
5657 Num_Disc
:= Num_Disc
+ 1;
5661 -- Insert stored discriminant associations in the correct
5662 -- order. If there are more stored discriminants than new
5663 -- discriminants, there is at least one new discriminant that
5664 -- constrains more than one of the stored discriminants. In
5665 -- this case we need to construct a proper subtype of the
5666 -- parent type, in order to supply values to all the
5667 -- components. Otherwise there is one-one correspondence
5668 -- between the constraints and the stored discriminants.
5670 First_Comp
:= Empty
;
5672 Discriminant
:= First_Stored_Discriminant
(Base_Type
(Typ
));
5673 while Present
(Discriminant
) loop
5674 Num_Gird
:= Num_Gird
+ 1;
5675 Next_Stored_Discriminant
(Discriminant
);
5678 -- Case of more stored discriminants than new discriminants
5680 if Num_Gird
> Num_Disc
then
5682 -- Create a proper subtype of the parent type, which is the
5683 -- proper implementation type for the aggregate, and convert
5684 -- it to the intended target type.
5686 Discriminant
:= First_Stored_Discriminant
(Base_Type
(Typ
));
5687 while Present
(Discriminant
) loop
5690 Get_Discriminant_Value
(
5693 Discriminant_Constraint
(Typ
)));
5694 Append
(New_Comp
, Constraints
);
5695 Next_Stored_Discriminant
(Discriminant
);
5699 Make_Subtype_Declaration
(Loc
,
5700 Defining_Identifier
=> Make_Temporary
(Loc
, 'T'),
5701 Subtype_Indication
=>
5702 Make_Subtype_Indication
(Loc
,
5704 New_Occurrence_Of
(Etype
(Base_Type
(Typ
)), Loc
),
5706 Make_Index_Or_Discriminant_Constraint
5707 (Loc
, Constraints
)));
5709 Insert_Action
(N
, Decl
);
5710 Prepend_Stored_Values
(Base_Type
(Typ
));
5712 Set_Etype
(N
, Defining_Identifier
(Decl
));
5715 Rewrite
(N
, Unchecked_Convert_To
(Typ
, N
));
5718 -- Case where we do not have fewer new discriminants than
5719 -- stored discriminants, so in this case we can simply use the
5720 -- stored discriminants of the subtype.
5723 Prepend_Stored_Values
(Typ
);
5725 end Generate_Aggregate_For_Derived_Type
;
5728 if Is_Tagged_Type
(Typ
) then
5730 -- The tagged case, _parent and _tag component must be created
5732 -- Reset null_present unconditionally. tagged records always have
5733 -- at least one field (the tag or the parent)
5735 Set_Null_Record_Present
(N
, False);
5737 -- When the current aggregate comes from the expansion of an
5738 -- extension aggregate, the parent expr is replaced by an
5739 -- aggregate formed by selected components of this expr
5741 if Present
(Parent_Expr
)
5742 and then Is_Empty_List
(Comps
)
5744 Comp
:= First_Component_Or_Discriminant
(Typ
);
5745 while Present
(Comp
) loop
5747 -- Skip all expander-generated components
5750 not Comes_From_Source
(Original_Record_Component
(Comp
))
5756 Make_Selected_Component
(Loc
,
5758 Unchecked_Convert_To
(Typ
,
5759 Duplicate_Subexpr
(Parent_Expr
, True)),
5761 Selector_Name
=> New_Occurrence_Of
(Comp
, Loc
));
5764 Make_Component_Association
(Loc
,
5766 New_List
(New_Occurrence_Of
(Comp
, Loc
)),
5770 Analyze_And_Resolve
(New_Comp
, Etype
(Comp
));
5773 Next_Component_Or_Discriminant
(Comp
);
5777 -- Compute the value for the Tag now, if the type is a root it
5778 -- will be included in the aggregate right away, otherwise it will
5779 -- be propagated to the parent aggregate
5781 if Present
(Orig_Tag
) then
5782 Tag_Value
:= Orig_Tag
;
5783 elsif not Tagged_Type_Expansion
then
5788 (Node
(First_Elmt
(Access_Disp_Table
(Typ
))), Loc
);
5791 -- For a derived type, an aggregate for the parent is formed with
5792 -- all the inherited components.
5794 if Is_Derived_Type
(Typ
) then
5797 First_Comp
: Node_Id
;
5798 Parent_Comps
: List_Id
;
5799 Parent_Aggr
: Node_Id
;
5800 Parent_Name
: Node_Id
;
5803 -- Remove the inherited component association from the
5804 -- aggregate and store them in the parent aggregate
5806 First_Comp
:= First
(Component_Associations
(N
));
5807 Parent_Comps
:= New_List
;
5808 while Present
(First_Comp
)
5809 and then Scope
(Original_Record_Component
(
5810 Entity
(First
(Choices
(First_Comp
))))) /= Base_Typ
5815 Append
(Comp
, Parent_Comps
);
5818 Parent_Aggr
:= Make_Aggregate
(Loc
,
5819 Component_Associations
=> Parent_Comps
);
5820 Set_Etype
(Parent_Aggr
, Etype
(Base_Type
(Typ
)));
5822 -- Find the _parent component
5824 Comp
:= First_Component
(Typ
);
5825 while Chars
(Comp
) /= Name_uParent
loop
5826 Comp
:= Next_Component
(Comp
);
5829 Parent_Name
:= New_Occurrence_Of
(Comp
, Loc
);
5831 -- Insert the parent aggregate
5833 Prepend_To
(Component_Associations
(N
),
5834 Make_Component_Association
(Loc
,
5835 Choices
=> New_List
(Parent_Name
),
5836 Expression
=> Parent_Aggr
));
5838 -- Expand recursively the parent propagating the right Tag
5840 Expand_Record_Aggregate
(
5841 Parent_Aggr
, Tag_Value
, Parent_Expr
);
5844 -- For a root type, the tag component is added (unless compiling
5845 -- for the VMs, where tags are implicit).
5847 elsif Tagged_Type_Expansion
then
5849 Tag_Name
: constant Node_Id
:=
5851 (First_Tag_Component
(Typ
), Loc
);
5852 Typ_Tag
: constant Entity_Id
:= RTE
(RE_Tag
);
5853 Conv_Node
: constant Node_Id
:=
5854 Unchecked_Convert_To
(Typ_Tag
, Tag_Value
);
5857 Set_Etype
(Conv_Node
, Typ_Tag
);
5858 Prepend_To
(Component_Associations
(N
),
5859 Make_Component_Association
(Loc
,
5860 Choices
=> New_List
(Tag_Name
),
5861 Expression
=> Conv_Node
));
5867 end Expand_Record_Aggregate
;
5869 ----------------------------
5870 -- Has_Default_Init_Comps --
5871 ----------------------------
5873 function Has_Default_Init_Comps
(N
: Node_Id
) return Boolean is
5874 Comps
: constant List_Id
:= Component_Associations
(N
);
5878 pragma Assert
(Nkind_In
(N
, N_Aggregate
, N_Extension_Aggregate
));
5884 if Has_Self_Reference
(N
) then
5888 -- Check if any direct component has default initialized components
5891 while Present
(C
) loop
5892 if Box_Present
(C
) then
5899 -- Recursive call in case of aggregate expression
5902 while Present
(C
) loop
5903 Expr
:= Expression
(C
);
5907 Nkind_In
(Expr
, N_Aggregate
, N_Extension_Aggregate
)
5908 and then Has_Default_Init_Comps
(Expr
)
5917 end Has_Default_Init_Comps
;
5919 --------------------------
5920 -- Is_Delayed_Aggregate --
5921 --------------------------
5923 function Is_Delayed_Aggregate
(N
: Node_Id
) return Boolean is
5924 Node
: Node_Id
:= N
;
5925 Kind
: Node_Kind
:= Nkind
(Node
);
5928 if Kind
= N_Qualified_Expression
then
5929 Node
:= Expression
(Node
);
5930 Kind
:= Nkind
(Node
);
5933 if Kind
/= N_Aggregate
and then Kind
/= N_Extension_Aggregate
then
5936 return Expansion_Delayed
(Node
);
5938 end Is_Delayed_Aggregate
;
5940 ----------------------------------------
5941 -- Is_Static_Dispatch_Table_Aggregate --
5942 ----------------------------------------
5944 function Is_Static_Dispatch_Table_Aggregate
(N
: Node_Id
) return Boolean is
5945 Typ
: constant Entity_Id
:= Base_Type
(Etype
(N
));
5948 return Static_Dispatch_Tables
5949 and then Tagged_Type_Expansion
5950 and then RTU_Loaded
(Ada_Tags
)
5952 -- Avoid circularity when rebuilding the compiler
5954 and then Cunit_Entity
(Get_Source_Unit
(N
)) /= RTU_Entity
(Ada_Tags
)
5955 and then (Typ
= RTE
(RE_Dispatch_Table_Wrapper
)
5957 Typ
= RTE
(RE_Address_Array
)
5959 Typ
= RTE
(RE_Type_Specific_Data
)
5961 Typ
= RTE
(RE_Tag_Table
)
5963 (RTE_Available
(RE_Interface_Data
)
5964 and then Typ
= RTE
(RE_Interface_Data
))
5966 (RTE_Available
(RE_Interfaces_Array
)
5967 and then Typ
= RTE
(RE_Interfaces_Array
))
5969 (RTE_Available
(RE_Interface_Data_Element
)
5970 and then Typ
= RTE
(RE_Interface_Data_Element
)));
5971 end Is_Static_Dispatch_Table_Aggregate
;
5973 --------------------
5974 -- Late_Expansion --
5975 --------------------
5977 function Late_Expansion
5981 Flist
: Node_Id
:= Empty
;
5982 Obj
: Entity_Id
:= Empty
) return List_Id
5985 if Is_Record_Type
(Etype
(N
)) then
5986 return Build_Record_Aggr_Code
(N
, Typ
, Target
, Flist
, Obj
);
5988 else pragma Assert
(Is_Array_Type
(Etype
(N
)));
5990 Build_Array_Aggr_Code
5992 Ctype
=> Component_Type
(Etype
(N
)),
5993 Index
=> First_Index
(Typ
),
5995 Scalar_Comp
=> Is_Scalar_Type
(Component_Type
(Typ
)),
6001 ----------------------------------
6002 -- Make_OK_Assignment_Statement --
6003 ----------------------------------
6005 function Make_OK_Assignment_Statement
6008 Expression
: Node_Id
) return Node_Id
6011 Set_Assignment_OK
(Name
);
6013 return Make_Assignment_Statement
(Sloc
, Name
, Expression
);
6014 end Make_OK_Assignment_Statement
;
6016 -----------------------
6017 -- Number_Of_Choices --
6018 -----------------------
6020 function Number_Of_Choices
(N
: Node_Id
) return Nat
is
6024 Nb_Choices
: Nat
:= 0;
6027 if Present
(Expressions
(N
)) then
6031 Assoc
:= First
(Component_Associations
(N
));
6032 while Present
(Assoc
) loop
6033 Choice
:= First
(Choices
(Assoc
));
6034 while Present
(Choice
) loop
6035 if Nkind
(Choice
) /= N_Others_Choice
then
6036 Nb_Choices
:= Nb_Choices
+ 1;
6046 end Number_Of_Choices
;
6048 ------------------------------------
6049 -- Packed_Array_Aggregate_Handled --
6050 ------------------------------------
6052 -- The current version of this procedure will handle at compile time
6053 -- any array aggregate that meets these conditions:
6055 -- One dimensional, bit packed
6056 -- Underlying packed type is modular type
6057 -- Bounds are within 32-bit Int range
6058 -- All bounds and values are static
6060 function Packed_Array_Aggregate_Handled
(N
: Node_Id
) return Boolean is
6061 Loc
: constant Source_Ptr
:= Sloc
(N
);
6062 Typ
: constant Entity_Id
:= Etype
(N
);
6063 Ctyp
: constant Entity_Id
:= Component_Type
(Typ
);
6065 Not_Handled
: exception;
6066 -- Exception raised if this aggregate cannot be handled
6069 -- For now, handle only one dimensional bit packed arrays
6071 if not Is_Bit_Packed_Array
(Typ
)
6072 or else Number_Dimensions
(Typ
) > 1
6073 or else not Is_Modular_Integer_Type
(Packed_Array_Type
(Typ
))
6078 if not Is_Scalar_Type
(Component_Type
(Typ
))
6079 and then Has_Non_Standard_Rep
(Component_Type
(Typ
))
6085 Csiz
: constant Nat
:= UI_To_Int
(Component_Size
(Typ
));
6089 -- Bounds of index type
6093 -- Values of bounds if compile time known
6095 function Get_Component_Val
(N
: Node_Id
) return Uint
;
6096 -- Given a expression value N of the component type Ctyp, returns a
6097 -- value of Csiz (component size) bits representing this value. If
6098 -- the value is non-static or any other reason exists why the value
6099 -- cannot be returned, then Not_Handled is raised.
6101 -----------------------
6102 -- Get_Component_Val --
6103 -----------------------
6105 function Get_Component_Val
(N
: Node_Id
) return Uint
is
6109 -- We have to analyze the expression here before doing any further
6110 -- processing here. The analysis of such expressions is deferred
6111 -- till expansion to prevent some problems of premature analysis.
6113 Analyze_And_Resolve
(N
, Ctyp
);
6115 -- Must have a compile time value. String literals have to be
6116 -- converted into temporaries as well, because they cannot easily
6117 -- be converted into their bit representation.
6119 if not Compile_Time_Known_Value
(N
)
6120 or else Nkind
(N
) = N_String_Literal
6125 Val
:= Expr_Rep_Value
(N
);
6127 -- Adjust for bias, and strip proper number of bits
6129 if Has_Biased_Representation
(Ctyp
) then
6130 Val
:= Val
- Expr_Value
(Type_Low_Bound
(Ctyp
));
6133 return Val
mod Uint_2
** Csiz
;
6134 end Get_Component_Val
;
6136 -- Here we know we have a one dimensional bit packed array
6139 Get_Index_Bounds
(First_Index
(Typ
), Lo
, Hi
);
6141 -- Cannot do anything if bounds are dynamic
6143 if not Compile_Time_Known_Value
(Lo
)
6145 not Compile_Time_Known_Value
(Hi
)
6150 -- Or are silly out of range of int bounds
6152 Lob
:= Expr_Value
(Lo
);
6153 Hib
:= Expr_Value
(Hi
);
6155 if not UI_Is_In_Int_Range
(Lob
)
6157 not UI_Is_In_Int_Range
(Hib
)
6162 -- At this stage we have a suitable aggregate for handling at compile
6163 -- time (the only remaining checks are that the values of expressions
6164 -- in the aggregate are compile time known (check is performed by
6165 -- Get_Component_Val), and that any subtypes or ranges are statically
6168 -- If the aggregate is not fully positional at this stage, then
6169 -- convert it to positional form. Either this will fail, in which
6170 -- case we can do nothing, or it will succeed, in which case we have
6171 -- succeeded in handling the aggregate, or it will stay an aggregate,
6172 -- in which case we have failed to handle this case.
6174 if Present
(Component_Associations
(N
)) then
6175 Convert_To_Positional
6176 (N
, Max_Others_Replicate
=> 64, Handle_Bit_Packed
=> True);
6177 return Nkind
(N
) /= N_Aggregate
;
6180 -- Otherwise we are all positional, so convert to proper value
6183 Lov
: constant Int
:= UI_To_Int
(Lob
);
6184 Hiv
: constant Int
:= UI_To_Int
(Hib
);
6186 Len
: constant Nat
:= Int
'Max (0, Hiv
- Lov
+ 1);
6187 -- The length of the array (number of elements)
6189 Aggregate_Val
: Uint
;
6190 -- Value of aggregate. The value is set in the low order bits of
6191 -- this value. For the little-endian case, the values are stored
6192 -- from low-order to high-order and for the big-endian case the
6193 -- values are stored from high-order to low-order. Note that gigi
6194 -- will take care of the conversions to left justify the value in
6195 -- the big endian case (because of left justified modular type
6196 -- processing), so we do not have to worry about that here.
6199 -- Integer literal for resulting constructed value
6202 -- Shift count from low order for next value
6205 -- Shift increment for loop
6208 -- Next expression from positional parameters of aggregate
6211 -- For little endian, we fill up the low order bits of the target
6212 -- value. For big endian we fill up the high order bits of the
6213 -- target value (which is a left justified modular value).
6215 if Bytes_Big_Endian
xor Debug_Flag_8
then
6216 Shift
:= Csiz
* (Len
- 1);
6223 -- Loop to set the values
6226 Aggregate_Val
:= Uint_0
;
6228 Expr
:= First
(Expressions
(N
));
6229 Aggregate_Val
:= Get_Component_Val
(Expr
) * Uint_2
** Shift
;
6231 for J
in 2 .. Len
loop
6232 Shift
:= Shift
+ Incr
;
6235 Aggregate_Val
+ Get_Component_Val
(Expr
) * Uint_2
** Shift
;
6239 -- Now we can rewrite with the proper value
6242 Make_Integer_Literal
(Loc
,
6243 Intval
=> Aggregate_Val
);
6244 Set_Print_In_Hex
(Lit
);
6246 -- Construct the expression using this literal. Note that it is
6247 -- important to qualify the literal with its proper modular type
6248 -- since universal integer does not have the required range and
6249 -- also this is a left justified modular type, which is important
6250 -- in the big-endian case.
6253 Unchecked_Convert_To
(Typ
,
6254 Make_Qualified_Expression
(Loc
,
6256 New_Occurrence_Of
(Packed_Array_Type
(Typ
), Loc
),
6257 Expression
=> Lit
)));
6259 Analyze_And_Resolve
(N
, Typ
);
6267 end Packed_Array_Aggregate_Handled
;
6269 ----------------------------
6270 -- Has_Mutable_Components --
6271 ----------------------------
6273 function Has_Mutable_Components
(Typ
: Entity_Id
) return Boolean is
6277 Comp
:= First_Component
(Typ
);
6278 while Present
(Comp
) loop
6279 if Is_Record_Type
(Etype
(Comp
))
6280 and then Has_Discriminants
(Etype
(Comp
))
6281 and then not Is_Constrained
(Etype
(Comp
))
6286 Next_Component
(Comp
);
6290 end Has_Mutable_Components
;
6292 ------------------------------
6293 -- Initialize_Discriminants --
6294 ------------------------------
6296 procedure Initialize_Discriminants
(N
: Node_Id
; Typ
: Entity_Id
) is
6297 Loc
: constant Source_Ptr
:= Sloc
(N
);
6298 Bas
: constant Entity_Id
:= Base_Type
(Typ
);
6299 Par
: constant Entity_Id
:= Etype
(Bas
);
6300 Decl
: constant Node_Id
:= Parent
(Par
);
6304 if Is_Tagged_Type
(Bas
)
6305 and then Is_Derived_Type
(Bas
)
6306 and then Has_Discriminants
(Par
)
6307 and then Has_Discriminants
(Bas
)
6308 and then Number_Discriminants
(Bas
) /= Number_Discriminants
(Par
)
6309 and then Nkind
(Decl
) = N_Full_Type_Declaration
6310 and then Nkind
(Type_Definition
(Decl
)) = N_Record_Definition
6312 (Variant_Part
(Component_List
(Type_Definition
(Decl
))))
6313 and then Nkind
(N
) /= N_Extension_Aggregate
6316 -- Call init proc to set discriminants.
6317 -- There should eventually be a special procedure for this ???
6319 Ref
:= New_Reference_To
(Defining_Identifier
(N
), Loc
);
6320 Insert_Actions_After
(N
,
6321 Build_Initialization_Call
(Sloc
(N
), Ref
, Typ
));
6323 end Initialize_Discriminants
;
6330 (Obj_Type
: Entity_Id
;
6331 Typ
: Entity_Id
) return Boolean
6333 L1
, L2
, H1
, H2
: Node_Id
;
6335 -- No sliding if the type of the object is not established yet, if it is
6336 -- an unconstrained type whose actual subtype comes from the aggregate,
6337 -- or if the two types are identical.
6339 if not Is_Array_Type
(Obj_Type
) then
6342 elsif not Is_Constrained
(Obj_Type
) then
6345 elsif Typ
= Obj_Type
then
6349 -- Sliding can only occur along the first dimension
6351 Get_Index_Bounds
(First_Index
(Typ
), L1
, H1
);
6352 Get_Index_Bounds
(First_Index
(Obj_Type
), L2
, H2
);
6354 if not Is_Static_Expression
(L1
)
6355 or else not Is_Static_Expression
(L2
)
6356 or else not Is_Static_Expression
(H1
)
6357 or else not Is_Static_Expression
(H2
)
6361 return Expr_Value
(L1
) /= Expr_Value
(L2
)
6362 or else Expr_Value
(H1
) /= Expr_Value
(H2
);
6367 ---------------------------
6368 -- Safe_Slice_Assignment --
6369 ---------------------------
6371 function Safe_Slice_Assignment
(N
: Node_Id
) return Boolean is
6372 Loc
: constant Source_Ptr
:= Sloc
(Parent
(N
));
6373 Pref
: constant Node_Id
:= Prefix
(Name
(Parent
(N
)));
6374 Range_Node
: constant Node_Id
:= Discrete_Range
(Name
(Parent
(N
)));
6382 -- Generate: for J in Range loop Pref (J) := Expr; end loop;
6384 if Comes_From_Source
(N
)
6385 and then No
(Expressions
(N
))
6386 and then Nkind
(First
(Choices
(First
(Component_Associations
(N
)))))
6389 Expr
:= Expression
(First
(Component_Associations
(N
)));
6390 L_J
:= Make_Temporary
(Loc
, 'J');
6393 Make_Iteration_Scheme
(Loc
,
6394 Loop_Parameter_Specification
=>
6395 Make_Loop_Parameter_Specification
6397 Defining_Identifier
=> L_J
,
6398 Discrete_Subtype_Definition
=> Relocate_Node
(Range_Node
)));
6401 Make_Assignment_Statement
(Loc
,
6403 Make_Indexed_Component
(Loc
,
6404 Prefix
=> Relocate_Node
(Pref
),
6405 Expressions
=> New_List
(New_Occurrence_Of
(L_J
, Loc
))),
6406 Expression
=> Relocate_Node
(Expr
));
6408 -- Construct the final loop
6411 Make_Implicit_Loop_Statement
6412 (Node
=> Parent
(N
),
6413 Identifier
=> Empty
,
6414 Iteration_Scheme
=> L_Iter
,
6415 Statements
=> New_List
(L_Body
));
6417 -- Set type of aggregate to be type of lhs in assignment,
6418 -- to suppress redundant length checks.
6420 Set_Etype
(N
, Etype
(Name
(Parent
(N
))));
6422 Rewrite
(Parent
(N
), Stat
);
6423 Analyze
(Parent
(N
));
6429 end Safe_Slice_Assignment
;
6431 ---------------------
6432 -- Sort_Case_Table --
6433 ---------------------
6435 procedure Sort_Case_Table
(Case_Table
: in out Case_Table_Type
) is
6436 L
: constant Int
:= Case_Table
'First;
6437 U
: constant Int
:= Case_Table
'Last;
6445 T
:= Case_Table
(K
+ 1);
6449 and then Expr_Value
(Case_Table
(J
- 1).Choice_Lo
) >
6450 Expr_Value
(T
.Choice_Lo
)
6452 Case_Table
(J
) := Case_Table
(J
- 1);
6456 Case_Table
(J
) := T
;
6459 end Sort_Case_Table
;
6461 ----------------------------
6462 -- Static_Array_Aggregate --
6463 ----------------------------
6465 function Static_Array_Aggregate
(N
: Node_Id
) return Boolean is
6466 Bounds
: constant Node_Id
:= Aggregate_Bounds
(N
);
6468 Typ
: constant Entity_Id
:= Etype
(N
);
6469 Comp_Type
: constant Entity_Id
:= Component_Type
(Typ
);
6476 if Is_Tagged_Type
(Typ
)
6477 or else Is_Controlled
(Typ
)
6478 or else Is_Packed
(Typ
)
6484 and then Nkind
(Bounds
) = N_Range
6485 and then Nkind
(Low_Bound
(Bounds
)) = N_Integer_Literal
6486 and then Nkind
(High_Bound
(Bounds
)) = N_Integer_Literal
6488 Lo
:= Low_Bound
(Bounds
);
6489 Hi
:= High_Bound
(Bounds
);
6491 if No
(Component_Associations
(N
)) then
6493 -- Verify that all components are static integers
6495 Expr
:= First
(Expressions
(N
));
6496 while Present
(Expr
) loop
6497 if Nkind
(Expr
) /= N_Integer_Literal
then
6507 -- We allow only a single named association, either a static
6508 -- range or an others_clause, with a static expression.
6510 Expr
:= First
(Component_Associations
(N
));
6512 if Present
(Expressions
(N
)) then
6515 elsif Present
(Next
(Expr
)) then
6518 elsif Present
(Next
(First
(Choices
(Expr
)))) then
6522 -- The aggregate is static if all components are literals,
6523 -- or else all its components are static aggregates for the
6524 -- component type. We also limit the size of a static aggregate
6525 -- to prevent runaway static expressions.
6527 if Is_Array_Type
(Comp_Type
)
6528 or else Is_Record_Type
(Comp_Type
)
6530 if Nkind
(Expression
(Expr
)) /= N_Aggregate
6532 not Compile_Time_Known_Aggregate
(Expression
(Expr
))
6537 elsif Nkind
(Expression
(Expr
)) /= N_Integer_Literal
then
6540 elsif not Aggr_Size_OK
(N
, Typ
) then
6544 -- Create a positional aggregate with the right number of
6545 -- copies of the expression.
6547 Agg
:= Make_Aggregate
(Sloc
(N
), New_List
, No_List
);
6549 for I
in UI_To_Int
(Intval
(Lo
)) .. UI_To_Int
(Intval
(Hi
))
6552 (Expressions
(Agg
), New_Copy
(Expression
(Expr
)));
6554 -- The copied expression must be analyzed and resolved.
6555 -- Besides setting the type, this ensures that static
6556 -- expressions are appropriately marked as such.
6559 (Last
(Expressions
(Agg
)), Component_Type
(Typ
));
6562 Set_Aggregate_Bounds
(Agg
, Bounds
);
6563 Set_Etype
(Agg
, Typ
);
6566 Set_Compile_Time_Known_Aggregate
(N
);
6575 end Static_Array_Aggregate
;