1 ------------------------------------------------------------------------------
3 -- GNAT COMPILER COMPONENTS --
9 -- Copyright (C) 1992-2011, Free Software Foundation, Inc. --
11 -- GNAT is free software; you can redistribute it and/or modify it under --
12 -- terms of the GNU General Public License as published by the Free Soft- --
13 -- ware Foundation; either version 3, or (at your option) any later ver- --
14 -- sion. GNAT is distributed in the hope that it will be useful, but WITH- --
15 -- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY --
16 -- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License --
17 -- for more details. You should have received a copy of the GNU General --
18 -- Public License distributed with GNAT; see file COPYING3. If not, go to --
19 -- http://www.gnu.org/licenses for a complete copy of the license. --
21 -- GNAT was originally developed by the GNAT team at New York University. --
22 -- Extensive contributions were provided by Ada Core Technologies Inc. --
24 ------------------------------------------------------------------------------
26 with Atree
; use Atree
;
27 with Checks
; use Checks
;
28 with Debug
; use Debug
;
29 with Einfo
; use Einfo
;
30 with Elists
; use Elists
;
31 with Errout
; use Errout
;
32 with Expander
; use Expander
;
33 with Exp_Util
; use Exp_Util
;
34 with Exp_Ch3
; use Exp_Ch3
;
35 with Exp_Ch6
; use Exp_Ch6
;
36 with Exp_Ch7
; use Exp_Ch7
;
37 with Exp_Ch9
; use Exp_Ch9
;
38 with Exp_Disp
; use Exp_Disp
;
39 with Exp_Tss
; use Exp_Tss
;
40 with Fname
; use Fname
;
41 with Freeze
; use Freeze
;
42 with Itypes
; use Itypes
;
44 with Namet
; use Namet
;
45 with Nmake
; use Nmake
;
46 with Nlists
; use Nlists
;
48 with Restrict
; use Restrict
;
49 with Rident
; use Rident
;
50 with Rtsfind
; use Rtsfind
;
51 with Ttypes
; use Ttypes
;
53 with Sem_Aggr
; use Sem_Aggr
;
54 with Sem_Aux
; use Sem_Aux
;
55 with Sem_Ch3
; use Sem_Ch3
;
56 with Sem_Eval
; use Sem_Eval
;
57 with Sem_Res
; use Sem_Res
;
58 with Sem_Util
; use Sem_Util
;
59 with Sinfo
; use Sinfo
;
60 with Snames
; use Snames
;
61 with Stand
; use Stand
;
62 with Targparm
; use Targparm
;
63 with Tbuild
; use Tbuild
;
64 with Uintp
; use Uintp
;
66 package body Exp_Aggr
is
68 type Case_Bounds
is record
71 Choice_Node
: Node_Id
;
74 type Case_Table_Type
is array (Nat
range <>) of Case_Bounds
;
75 -- Table type used by Check_Case_Choices procedure
77 function Has_Default_Init_Comps
(N
: Node_Id
) return Boolean;
78 -- N is an aggregate (record or array). Checks the presence of default
79 -- initialization (<>) in any component (Ada 2005: AI-287).
81 function Is_Static_Dispatch_Table_Aggregate
(N
: Node_Id
) return Boolean;
82 -- Returns true if N is an aggregate used to initialize the components
83 -- of an statically allocated dispatch table.
86 (Obj_Type
: Entity_Id
;
87 Typ
: Entity_Id
) return Boolean;
88 -- A static array aggregate in an object declaration can in most cases be
89 -- expanded in place. The one exception is when the aggregate is given
90 -- with component associations that specify different bounds from those of
91 -- the type definition in the object declaration. In this pathological
92 -- case the aggregate must slide, and we must introduce an intermediate
93 -- temporary to hold it.
95 -- The same holds in an assignment to one-dimensional array of arrays,
96 -- when a component may be given with bounds that differ from those of the
99 procedure Sort_Case_Table
(Case_Table
: in out Case_Table_Type
);
100 -- Sort the Case Table using the Lower Bound of each Choice as the key.
101 -- A simple insertion sort is used since the number of choices in a case
102 -- statement of variant part will usually be small and probably in near
105 ------------------------------------------------------
106 -- Local subprograms for Record Aggregate Expansion --
107 ------------------------------------------------------
109 function Build_Record_Aggr_Code
112 Lhs
: Node_Id
) return List_Id
;
113 -- N is an N_Aggregate or an N_Extension_Aggregate. Typ is the type of the
114 -- aggregate. Target is an expression containing the location on which the
115 -- component by component assignments will take place. Returns the list of
116 -- assignments plus all other adjustments needed for tagged and controlled
119 procedure Convert_To_Assignments
(N
: Node_Id
; Typ
: Entity_Id
);
120 -- N is an N_Aggregate or an N_Extension_Aggregate. Typ is the type of the
121 -- aggregate (which can only be a record type, this procedure is only used
122 -- for record types). Transform the given aggregate into a sequence of
123 -- assignments performed component by component.
125 procedure Expand_Record_Aggregate
127 Orig_Tag
: Node_Id
:= Empty
;
128 Parent_Expr
: Node_Id
:= Empty
);
129 -- This is the top level procedure for record aggregate expansion.
130 -- Expansion for record aggregates needs expand aggregates for tagged
131 -- record types. Specifically Expand_Record_Aggregate adds the Tag
132 -- field in front of the Component_Association list that was created
133 -- during resolution by Resolve_Record_Aggregate.
135 -- N is the record aggregate node.
136 -- Orig_Tag is the value of the Tag that has to be provided for this
137 -- specific aggregate. It carries the tag corresponding to the type
138 -- of the outermost aggregate during the recursive expansion
139 -- Parent_Expr is the ancestor part of the original extension
142 function Has_Mutable_Components
(Typ
: Entity_Id
) return Boolean;
143 -- Return true if one of the component is of a discriminated type with
144 -- defaults. An aggregate for a type with mutable components must be
145 -- expanded into individual assignments.
147 procedure Initialize_Discriminants
(N
: Node_Id
; Typ
: Entity_Id
);
148 -- If the type of the aggregate is a type extension with renamed discrimi-
149 -- nants, we must initialize the hidden discriminants of the parent.
150 -- Otherwise, the target object must not be initialized. The discriminants
151 -- are initialized by calling the initialization procedure for the type.
152 -- This is incorrect if the initialization of other components has any
153 -- side effects. We restrict this call to the case where the parent type
154 -- has a variant part, because this is the only case where the hidden
155 -- discriminants are accessed, namely when calling discriminant checking
156 -- functions of the parent type, and when applying a stream attribute to
157 -- an object of the derived type.
159 -----------------------------------------------------
160 -- Local Subprograms for Array Aggregate Expansion --
161 -----------------------------------------------------
163 function Aggr_Size_OK
(N
: Node_Id
; Typ
: Entity_Id
) return Boolean;
164 -- Very large static aggregates present problems to the back-end, and are
165 -- transformed into assignments and loops. This function verifies that the
166 -- total number of components of an aggregate is acceptable for rewriting
167 -- into a purely positional static form. Aggr_Size_OK must be called before
170 -- This function also detects and warns about one-component aggregates that
171 -- appear in a non-static context. Even if the component value is static,
172 -- such an aggregate must be expanded into an assignment.
174 function Backend_Processing_Possible
(N
: Node_Id
) return Boolean;
175 -- This function checks if array aggregate N can be processed directly
176 -- by the backend. If this is the case True is returned.
178 function Build_Array_Aggr_Code
183 Scalar_Comp
: Boolean;
184 Indexes
: List_Id
:= No_List
) return List_Id
;
185 -- This recursive routine returns a list of statements containing the
186 -- loops and assignments that are needed for the expansion of the array
189 -- N is the (sub-)aggregate node to be expanded into code. This node has
190 -- been fully analyzed, and its Etype is properly set.
192 -- Index is the index node corresponding to the array sub-aggregate N
194 -- Into is the target expression into which we are copying the aggregate.
195 -- Note that this node may not have been analyzed yet, and so the Etype
196 -- field may not be set.
198 -- Scalar_Comp is True if the component type of the aggregate is scalar
200 -- Indexes is the current list of expressions used to index the object we
203 procedure Convert_Array_Aggr_In_Allocator
207 -- If the aggregate appears within an allocator and can be expanded in
208 -- place, this routine generates the individual assignments to components
209 -- of the designated object. This is an optimization over the general
210 -- case, where a temporary is first created on the stack and then used to
211 -- construct the allocated object on the heap.
213 procedure Convert_To_Positional
215 Max_Others_Replicate
: Nat
:= 5;
216 Handle_Bit_Packed
: Boolean := False);
217 -- If possible, convert named notation to positional notation. This
218 -- conversion is possible only in some static cases. If the conversion is
219 -- possible, then N is rewritten with the analyzed converted aggregate.
220 -- The parameter Max_Others_Replicate controls the maximum number of
221 -- values corresponding to an others choice that will be converted to
222 -- positional notation (the default of 5 is the normal limit, and reflects
223 -- the fact that normally the loop is better than a lot of separate
224 -- assignments). Note that this limit gets overridden in any case if
225 -- either of the restrictions No_Elaboration_Code or No_Implicit_Loops is
226 -- set. The parameter Handle_Bit_Packed is usually set False (since we do
227 -- not expect the back end to handle bit packed arrays, so the normal case
228 -- of conversion is pointless), but in the special case of a call from
229 -- Packed_Array_Aggregate_Handled, we set this parameter to True, since
230 -- these are cases we handle in there.
232 -- It would seem worthwhile to have a higher default value for Max_Others_
233 -- replicate, but aggregates in the compiler make this impossible: the
234 -- compiler bootstrap fails if Max_Others_Replicate is greater than 25.
235 -- This is unexpected ???
237 procedure Expand_Array_Aggregate
(N
: Node_Id
);
238 -- This is the top-level routine to perform array aggregate expansion.
239 -- N is the N_Aggregate node to be expanded.
241 function Late_Expansion
244 Target
: Node_Id
) return List_Id
;
245 -- This routine implements top-down expansion of nested aggregates. In
246 -- doing so, it avoids the generation of temporaries at each level. N is a
247 -- nested (record or array) aggregate that has been marked with 'Delay_
248 -- Expansion'. Typ is the expected type of the aggregate. Target is a
249 -- (duplicable) expression that will hold the result of the aggregate
252 function Make_OK_Assignment_Statement
255 Expression
: Node_Id
) return Node_Id
;
256 -- This is like Make_Assignment_Statement, except that Assignment_OK
257 -- is set in the left operand. All assignments built by this unit
258 -- use this routine. This is needed to deal with assignments to
259 -- initialized constants that are done in place.
261 function Number_Of_Choices
(N
: Node_Id
) return Nat
;
262 -- Returns the number of discrete choices (not including the others choice
263 -- if present) contained in (sub-)aggregate N.
265 function Packed_Array_Aggregate_Handled
(N
: Node_Id
) return Boolean;
266 -- Given an array aggregate, this function handles the case of a packed
267 -- array aggregate with all constant values, where the aggregate can be
268 -- evaluated at compile time. If this is possible, then N is rewritten
269 -- to be its proper compile time value with all the components properly
270 -- assembled. The expression is analyzed and resolved and True is
271 -- returned. If this transformation is not possible, N is unchanged
272 -- and False is returned
274 function Safe_Slice_Assignment
(N
: Node_Id
) return Boolean;
275 -- If a slice assignment has an aggregate with a single others_choice,
276 -- the assignment can be done in place even if bounds are not static,
277 -- by converting it into a loop over the discrete range of the slice.
283 function Aggr_Size_OK
(N
: Node_Id
; Typ
: Entity_Id
) return Boolean is
291 -- The following constant determines the maximum size of an array
292 -- aggregate produced by converting named to positional notation (e.g.
293 -- from others clauses). This avoids running away with attempts to
294 -- convert huge aggregates, which hit memory limits in the backend.
296 -- The normal limit is 5000, but we increase this limit to 2**24 (about
297 -- 16 million) if Restrictions (No_Elaboration_Code) or Restrictions
298 -- (No_Implicit_Loops) is specified, since in either case, we are at
299 -- risk of declaring the program illegal because of this limit.
301 Max_Aggr_Size
: constant Nat
:=
302 5000 + (2 ** 24 - 5000) *
304 (Restriction_Active
(No_Elaboration_Code
)
306 Restriction_Active
(No_Implicit_Loops
));
308 function Component_Count
(T
: Entity_Id
) return Int
;
309 -- The limit is applied to the total number of components that the
310 -- aggregate will have, which is the number of static expressions
311 -- that will appear in the flattened array. This requires a recursive
312 -- computation of the number of scalar components of the structure.
314 ---------------------
315 -- Component_Count --
316 ---------------------
318 function Component_Count
(T
: Entity_Id
) return Int
is
323 if Is_Scalar_Type
(T
) then
326 elsif Is_Record_Type
(T
) then
327 Comp
:= First_Component
(T
);
328 while Present
(Comp
) loop
329 Res
:= Res
+ Component_Count
(Etype
(Comp
));
330 Next_Component
(Comp
);
335 elsif Is_Array_Type
(T
) then
337 Lo
: constant Node_Id
:=
338 Type_Low_Bound
(Etype
(First_Index
(T
)));
339 Hi
: constant Node_Id
:=
340 Type_High_Bound
(Etype
(First_Index
(T
)));
342 Siz
: constant Int
:= Component_Count
(Component_Type
(T
));
345 if not Compile_Time_Known_Value
(Lo
)
346 or else not Compile_Time_Known_Value
(Hi
)
351 Siz
* UI_To_Int
(Expr_Value
(Hi
) - Expr_Value
(Lo
) + 1);
356 -- Can only be a null for an access type
362 -- Start of processing for Aggr_Size_OK
365 Siz
:= Component_Count
(Component_Type
(Typ
));
367 Indx
:= First_Index
(Typ
);
368 while Present
(Indx
) loop
369 Lo
:= Type_Low_Bound
(Etype
(Indx
));
370 Hi
:= Type_High_Bound
(Etype
(Indx
));
372 -- Bounds need to be known at compile time
374 if not Compile_Time_Known_Value
(Lo
)
375 or else not Compile_Time_Known_Value
(Hi
)
380 Lov
:= Expr_Value
(Lo
);
381 Hiv
:= Expr_Value
(Hi
);
383 -- A flat array is always safe
389 -- One-component aggregates are suspicious, and if the context type
390 -- is an object declaration with non-static bounds it will trip gcc;
391 -- such an aggregate must be expanded into a single assignment.
394 and then Nkind
(Parent
(N
)) = N_Object_Declaration
397 Index_Type
: constant Entity_Id
:=
400 (Etype
(Defining_Identifier
(Parent
(N
)))));
404 if not Compile_Time_Known_Value
(Type_Low_Bound
(Index_Type
))
405 or else not Compile_Time_Known_Value
406 (Type_High_Bound
(Index_Type
))
408 if Present
(Component_Associations
(N
)) then
410 First
(Choices
(First
(Component_Associations
(N
))));
411 if Is_Entity_Name
(Indx
)
412 and then not Is_Type
(Entity
(Indx
))
415 ("single component aggregate in non-static context?",
417 Error_Msg_N
("\maybe subtype name was meant?", Indx
);
427 Rng
: constant Uint
:= Hiv
- Lov
+ 1;
430 -- Check if size is too large
432 if not UI_Is_In_Int_Range
(Rng
) then
436 Siz
:= Siz
* UI_To_Int
(Rng
);
440 or else Siz
> Max_Aggr_Size
445 -- Bounds must be in integer range, for later array construction
447 if not UI_Is_In_Int_Range
(Lov
)
449 not UI_Is_In_Int_Range
(Hiv
)
460 ---------------------------------
461 -- Backend_Processing_Possible --
462 ---------------------------------
464 -- Backend processing by Gigi/gcc is possible only if all the following
465 -- conditions are met:
467 -- 1. N is fully positional
469 -- 2. N is not a bit-packed array aggregate;
471 -- 3. The size of N's array type must be known at compile time. Note
472 -- that this implies that the component size is also known
474 -- 4. The array type of N does not follow the Fortran layout convention
475 -- or if it does it must be 1 dimensional.
477 -- 5. The array component type may not be tagged (which could necessitate
478 -- reassignment of proper tags).
480 -- 6. The array component type must not have unaligned bit components
482 -- 7. None of the components of the aggregate may be bit unaligned
485 -- 8. There cannot be delayed components, since we do not know enough
486 -- at this stage to know if back end processing is possible.
488 -- 9. There cannot be any discriminated record components, since the
489 -- back end cannot handle this complex case.
491 -- 10. No controlled actions need to be generated for components
493 -- 11. For a VM back end, the array should have no aliased components
495 function Backend_Processing_Possible
(N
: Node_Id
) return Boolean is
496 Typ
: constant Entity_Id
:= Etype
(N
);
497 -- Typ is the correct constrained array subtype of the aggregate
499 function Component_Check
(N
: Node_Id
; Index
: Node_Id
) return Boolean;
500 -- This routine checks components of aggregate N, enforcing checks
501 -- 1, 7, 8, and 9. In the multi-dimensional case, these checks are
502 -- performed on subaggregates. The Index value is the current index
503 -- being checked in the multi-dimensional case.
505 ---------------------
506 -- Component_Check --
507 ---------------------
509 function Component_Check
(N
: Node_Id
; Index
: Node_Id
) return Boolean is
513 -- Checks 1: (no component associations)
515 if Present
(Component_Associations
(N
)) then
519 -- Checks on components
521 -- Recurse to check subaggregates, which may appear in qualified
522 -- expressions. If delayed, the front-end will have to expand.
523 -- If the component is a discriminated record, treat as non-static,
524 -- as the back-end cannot handle this properly.
526 Expr
:= First
(Expressions
(N
));
527 while Present
(Expr
) loop
529 -- Checks 8: (no delayed components)
531 if Is_Delayed_Aggregate
(Expr
) then
535 -- Checks 9: (no discriminated records)
537 if Present
(Etype
(Expr
))
538 and then Is_Record_Type
(Etype
(Expr
))
539 and then Has_Discriminants
(Etype
(Expr
))
544 -- Checks 7. Component must not be bit aligned component
546 if Possible_Bit_Aligned_Component
(Expr
) then
550 -- Recursion to following indexes for multiple dimension case
552 if Present
(Next_Index
(Index
))
553 and then not Component_Check
(Expr
, Next_Index
(Index
))
558 -- All checks for that component finished, on to next
566 -- Start of processing for Backend_Processing_Possible
569 -- Checks 2 (array not bit packed) and 10 (no controlled actions)
571 if Is_Bit_Packed_Array
(Typ
) or else Needs_Finalization
(Typ
) then
575 -- If component is limited, aggregate must be expanded because each
576 -- component assignment must be built in place.
578 if Is_Immutably_Limited_Type
(Component_Type
(Typ
)) then
582 -- Checks 4 (array must not be multi-dimensional Fortran case)
584 if Convention
(Typ
) = Convention_Fortran
585 and then Number_Dimensions
(Typ
) > 1
590 -- Checks 3 (size of array must be known at compile time)
592 if not Size_Known_At_Compile_Time
(Typ
) then
596 -- Checks on components
598 if not Component_Check
(N
, First_Index
(Typ
)) then
602 -- Checks 5 (if the component type is tagged, then we may need to do
603 -- tag adjustments. Perhaps this should be refined to check for any
604 -- component associations that actually need tag adjustment, similar
605 -- to the test in Component_Not_OK_For_Backend for record aggregates
606 -- with tagged components, but not clear whether it's worthwhile ???;
607 -- in the case of the JVM, object tags are handled implicitly)
609 if Is_Tagged_Type
(Component_Type
(Typ
))
610 and then Tagged_Type_Expansion
615 -- Checks 6 (component type must not have bit aligned components)
617 if Type_May_Have_Bit_Aligned_Components
(Component_Type
(Typ
)) then
621 -- Checks 11: Array aggregates with aliased components are currently
622 -- not well supported by the VM backend; disable temporarily this
623 -- backend processing until it is definitely supported.
625 if VM_Target
/= No_VM
626 and then Has_Aliased_Components
(Base_Type
(Typ
))
631 -- Backend processing is possible
633 Set_Size_Known_At_Compile_Time
(Etype
(N
), True);
635 end Backend_Processing_Possible
;
637 ---------------------------
638 -- Build_Array_Aggr_Code --
639 ---------------------------
641 -- The code that we generate from a one dimensional aggregate is
643 -- 1. If the sub-aggregate contains discrete choices we
645 -- (a) Sort the discrete choices
647 -- (b) Otherwise for each discrete choice that specifies a range we
648 -- emit a loop. If a range specifies a maximum of three values, or
649 -- we are dealing with an expression we emit a sequence of
650 -- assignments instead of a loop.
652 -- (c) Generate the remaining loops to cover the others choice if any
654 -- 2. If the aggregate contains positional elements we
656 -- (a) translate the positional elements in a series of assignments
658 -- (b) Generate a final loop to cover the others choice if any.
659 -- Note that this final loop has to be a while loop since the case
661 -- L : Integer := Integer'Last;
662 -- H : Integer := Integer'Last;
663 -- A : array (L .. H) := (1, others =>0);
665 -- cannot be handled by a for loop. Thus for the following
667 -- array (L .. H) := (.. positional elements.., others =>E);
669 -- we always generate something like:
671 -- J : Index_Type := Index_Of_Last_Positional_Element;
673 -- J := Index_Base'Succ (J)
677 function Build_Array_Aggr_Code
682 Scalar_Comp
: Boolean;
683 Indexes
: List_Id
:= No_List
) return List_Id
685 Loc
: constant Source_Ptr
:= Sloc
(N
);
686 Index_Base
: constant Entity_Id
:= Base_Type
(Etype
(Index
));
687 Index_Base_L
: constant Node_Id
:= Type_Low_Bound
(Index_Base
);
688 Index_Base_H
: constant Node_Id
:= Type_High_Bound
(Index_Base
);
690 function Add
(Val
: Int
; To
: Node_Id
) return Node_Id
;
691 -- Returns an expression where Val is added to expression To, unless
692 -- To+Val is provably out of To's base type range. To must be an
693 -- already analyzed expression.
695 function Empty_Range
(L
, H
: Node_Id
) return Boolean;
696 -- Returns True if the range defined by L .. H is certainly empty
698 function Equal
(L
, H
: Node_Id
) return Boolean;
699 -- Returns True if L = H for sure
701 function Index_Base_Name
return Node_Id
;
702 -- Returns a new reference to the index type name
704 function Gen_Assign
(Ind
: Node_Id
; Expr
: Node_Id
) return List_Id
;
705 -- Ind must be a side-effect free expression. If the input aggregate
706 -- N to Build_Loop contains no sub-aggregates, then this function
707 -- returns the assignment statement:
709 -- Into (Indexes, Ind) := Expr;
711 -- Otherwise we call Build_Code recursively
713 -- Ada 2005 (AI-287): In case of default initialized component, Expr
714 -- is empty and we generate a call to the corresponding IP subprogram.
716 function Gen_Loop
(L
, H
: Node_Id
; Expr
: Node_Id
) return List_Id
;
717 -- Nodes L and H must be side-effect free expressions.
718 -- If the input aggregate N to Build_Loop contains no sub-aggregates,
719 -- This routine returns the for loop statement
721 -- for J in Index_Base'(L) .. Index_Base'(H) loop
722 -- Into (Indexes, J) := Expr;
725 -- Otherwise we call Build_Code recursively.
726 -- As an optimization if the loop covers 3 or less scalar elements we
727 -- generate a sequence of assignments.
729 function Gen_While
(L
, H
: Node_Id
; Expr
: Node_Id
) return List_Id
;
730 -- Nodes L and H must be side-effect free expressions.
731 -- If the input aggregate N to Build_Loop contains no sub-aggregates,
732 -- This routine returns the while loop statement
734 -- J : Index_Base := L;
736 -- J := Index_Base'Succ (J);
737 -- Into (Indexes, J) := Expr;
740 -- Otherwise we call Build_Code recursively
742 function Local_Compile_Time_Known_Value
(E
: Node_Id
) return Boolean;
743 function Local_Expr_Value
(E
: Node_Id
) return Uint
;
744 -- These two Local routines are used to replace the corresponding ones
745 -- in sem_eval because while processing the bounds of an aggregate with
746 -- discrete choices whose index type is an enumeration, we build static
747 -- expressions not recognized by Compile_Time_Known_Value as such since
748 -- they have not yet been analyzed and resolved. All the expressions in
749 -- question are things like Index_Base_Name'Val (Const) which we can
750 -- easily recognize as being constant.
756 function Add
(Val
: Int
; To
: Node_Id
) return Node_Id
is
761 U_Val
: constant Uint
:= UI_From_Int
(Val
);
764 -- Note: do not try to optimize the case of Val = 0, because
765 -- we need to build a new node with the proper Sloc value anyway.
767 -- First test if we can do constant folding
769 if Local_Compile_Time_Known_Value
(To
) then
770 U_To
:= Local_Expr_Value
(To
) + Val
;
772 -- Determine if our constant is outside the range of the index.
773 -- If so return an Empty node. This empty node will be caught
774 -- by Empty_Range below.
776 if Compile_Time_Known_Value
(Index_Base_L
)
777 and then U_To
< Expr_Value
(Index_Base_L
)
781 elsif Compile_Time_Known_Value
(Index_Base_H
)
782 and then U_To
> Expr_Value
(Index_Base_H
)
787 Expr_Pos
:= Make_Integer_Literal
(Loc
, U_To
);
788 Set_Is_Static_Expression
(Expr_Pos
);
790 if not Is_Enumeration_Type
(Index_Base
) then
793 -- If we are dealing with enumeration return
794 -- Index_Base'Val (Expr_Pos)
798 Make_Attribute_Reference
800 Prefix
=> Index_Base_Name
,
801 Attribute_Name
=> Name_Val
,
802 Expressions
=> New_List
(Expr_Pos
));
808 -- If we are here no constant folding possible
810 if not Is_Enumeration_Type
(Index_Base
) then
813 Left_Opnd
=> Duplicate_Subexpr
(To
),
814 Right_Opnd
=> Make_Integer_Literal
(Loc
, U_Val
));
816 -- If we are dealing with enumeration return
817 -- Index_Base'Val (Index_Base'Pos (To) + Val)
821 Make_Attribute_Reference
823 Prefix
=> Index_Base_Name
,
824 Attribute_Name
=> Name_Pos
,
825 Expressions
=> New_List
(Duplicate_Subexpr
(To
)));
830 Right_Opnd
=> Make_Integer_Literal
(Loc
, U_Val
));
833 Make_Attribute_Reference
835 Prefix
=> Index_Base_Name
,
836 Attribute_Name
=> Name_Val
,
837 Expressions
=> New_List
(Expr_Pos
));
847 function Empty_Range
(L
, H
: Node_Id
) return Boolean is
848 Is_Empty
: Boolean := False;
853 -- First check if L or H were already detected as overflowing the
854 -- index base range type by function Add above. If this is so Add
855 -- returns the empty node.
857 if No
(L
) or else No
(H
) then
864 -- L > H range is empty
870 -- B_L > H range must be empty
876 -- L > B_H range must be empty
880 High
:= Index_Base_H
;
883 if Local_Compile_Time_Known_Value
(Low
)
884 and then Local_Compile_Time_Known_Value
(High
)
887 UI_Gt
(Local_Expr_Value
(Low
), Local_Expr_Value
(High
));
900 function Equal
(L
, H
: Node_Id
) return Boolean is
905 elsif Local_Compile_Time_Known_Value
(L
)
906 and then Local_Compile_Time_Known_Value
(H
)
908 return UI_Eq
(Local_Expr_Value
(L
), Local_Expr_Value
(H
));
918 function Gen_Assign
(Ind
: Node_Id
; Expr
: Node_Id
) return List_Id
is
919 L
: constant List_Id
:= New_List
;
922 New_Indexes
: List_Id
;
923 Indexed_Comp
: Node_Id
;
925 Comp_Type
: Entity_Id
:= Empty
;
927 function Add_Loop_Actions
(Lis
: List_Id
) return List_Id
;
928 -- Collect insert_actions generated in the construction of a
929 -- loop, and prepend them to the sequence of assignments to
930 -- complete the eventual body of the loop.
932 ----------------------
933 -- Add_Loop_Actions --
934 ----------------------
936 function Add_Loop_Actions
(Lis
: List_Id
) return List_Id
is
940 -- Ada 2005 (AI-287): Do nothing else in case of default
941 -- initialized component.
946 elsif Nkind
(Parent
(Expr
)) = N_Component_Association
947 and then Present
(Loop_Actions
(Parent
(Expr
)))
949 Append_List
(Lis
, Loop_Actions
(Parent
(Expr
)));
950 Res
:= Loop_Actions
(Parent
(Expr
));
951 Set_Loop_Actions
(Parent
(Expr
), No_List
);
957 end Add_Loop_Actions
;
959 -- Start of processing for Gen_Assign
963 New_Indexes
:= New_List
;
965 New_Indexes
:= New_Copy_List_Tree
(Indexes
);
968 Append_To
(New_Indexes
, Ind
);
970 if Present
(Next_Index
(Index
)) then
973 Build_Array_Aggr_Code
976 Index
=> Next_Index
(Index
),
978 Scalar_Comp
=> Scalar_Comp
,
979 Indexes
=> New_Indexes
));
982 -- If we get here then we are at a bottom-level (sub-)aggregate
986 (Make_Indexed_Component
(Loc
,
987 Prefix
=> New_Copy_Tree
(Into
),
988 Expressions
=> New_Indexes
));
990 Set_Assignment_OK
(Indexed_Comp
);
992 -- Ada 2005 (AI-287): In case of default initialized component, Expr
993 -- is not present (and therefore we also initialize Expr_Q to empty).
997 elsif Nkind
(Expr
) = N_Qualified_Expression
then
998 Expr_Q
:= Expression
(Expr
);
1003 if Present
(Etype
(N
))
1004 and then Etype
(N
) /= Any_Composite
1006 Comp_Type
:= Component_Type
(Etype
(N
));
1007 pragma Assert
(Comp_Type
= Ctype
); -- AI-287
1009 elsif Present
(Next
(First
(New_Indexes
))) then
1011 -- Ada 2005 (AI-287): Do nothing in case of default initialized
1012 -- component because we have received the component type in
1013 -- the formal parameter Ctype.
1015 -- ??? Some assert pragmas have been added to check if this new
1016 -- formal can be used to replace this code in all cases.
1018 if Present
(Expr
) then
1020 -- This is a multidimensional array. Recover the component
1021 -- type from the outermost aggregate, because subaggregates
1022 -- do not have an assigned type.
1029 while Present
(P
) loop
1030 if Nkind
(P
) = N_Aggregate
1031 and then Present
(Etype
(P
))
1033 Comp_Type
:= Component_Type
(Etype
(P
));
1041 pragma Assert
(Comp_Type
= Ctype
); -- AI-287
1046 -- Ada 2005 (AI-287): We only analyze the expression in case of non-
1047 -- default initialized components (otherwise Expr_Q is not present).
1050 and then Nkind_In
(Expr_Q
, N_Aggregate
, N_Extension_Aggregate
)
1052 -- At this stage the Expression may not have been analyzed yet
1053 -- because the array aggregate code has not been updated to use
1054 -- the Expansion_Delayed flag and avoid analysis altogether to
1055 -- solve the same problem (see Resolve_Aggr_Expr). So let us do
1056 -- the analysis of non-array aggregates now in order to get the
1057 -- value of Expansion_Delayed flag for the inner aggregate ???
1059 if Present
(Comp_Type
) and then not Is_Array_Type
(Comp_Type
) then
1060 Analyze_And_Resolve
(Expr_Q
, Comp_Type
);
1063 if Is_Delayed_Aggregate
(Expr_Q
) then
1065 -- This is either a subaggregate of a multidimensional array,
1066 -- or a component of an array type whose component type is
1067 -- also an array. In the latter case, the expression may have
1068 -- component associations that provide different bounds from
1069 -- those of the component type, and sliding must occur. Instead
1070 -- of decomposing the current aggregate assignment, force the
1071 -- re-analysis of the assignment, so that a temporary will be
1072 -- generated in the usual fashion, and sliding will take place.
1074 if Nkind
(Parent
(N
)) = N_Assignment_Statement
1075 and then Is_Array_Type
(Comp_Type
)
1076 and then Present
(Component_Associations
(Expr_Q
))
1077 and then Must_Slide
(Comp_Type
, Etype
(Expr_Q
))
1079 Set_Expansion_Delayed
(Expr_Q
, False);
1080 Set_Analyzed
(Expr_Q
, False);
1085 Late_Expansion
(Expr_Q
, Etype
(Expr_Q
), Indexed_Comp
));
1090 -- Ada 2005 (AI-287): In case of default initialized component, call
1091 -- the initialization subprogram associated with the component type.
1092 -- If the component type is an access type, add an explicit null
1093 -- assignment, because for the back-end there is an initialization
1094 -- present for the whole aggregate, and no default initialization
1097 -- In addition, if the component type is controlled, we must call
1098 -- its Initialize procedure explicitly, because there is no explicit
1099 -- object creation that will invoke it otherwise.
1102 if Present
(Base_Init_Proc
(Base_Type
(Ctype
)))
1103 or else Has_Task
(Base_Type
(Ctype
))
1106 Build_Initialization_Call
(Loc
,
1107 Id_Ref
=> Indexed_Comp
,
1109 With_Default_Init
=> True));
1111 elsif Is_Access_Type
(Ctype
) then
1113 Make_Assignment_Statement
(Loc
,
1114 Name
=> Indexed_Comp
,
1115 Expression
=> Make_Null
(Loc
)));
1118 if Needs_Finalization
(Ctype
) then
1121 Obj_Ref
=> New_Copy_Tree
(Indexed_Comp
),
1126 -- Now generate the assignment with no associated controlled
1127 -- actions since the target of the assignment may not have been
1128 -- initialized, it is not possible to Finalize it as expected by
1129 -- normal controlled assignment. The rest of the controlled
1130 -- actions are done manually with the proper finalization list
1131 -- coming from the context.
1134 Make_OK_Assignment_Statement
(Loc
,
1135 Name
=> Indexed_Comp
,
1136 Expression
=> New_Copy_Tree
(Expr
));
1138 if Present
(Comp_Type
) and then Needs_Finalization
(Comp_Type
) then
1139 Set_No_Ctrl_Actions
(A
);
1141 -- If this is an aggregate for an array of arrays, each
1142 -- sub-aggregate will be expanded as well, and even with
1143 -- No_Ctrl_Actions the assignments of inner components will
1144 -- require attachment in their assignments to temporaries.
1145 -- These temporaries must be finalized for each subaggregate,
1146 -- to prevent multiple attachments of the same temporary
1147 -- location to same finalization chain (and consequently
1148 -- circular lists). To ensure that finalization takes place
1149 -- for each subaggregate we wrap the assignment in a block.
1151 if Is_Array_Type
(Comp_Type
)
1152 and then Nkind
(Expr
) = N_Aggregate
1155 Make_Block_Statement
(Loc
,
1156 Handled_Statement_Sequence
=>
1157 Make_Handled_Sequence_Of_Statements
(Loc
,
1158 Statements
=> New_List
(A
)));
1164 -- Adjust the tag if tagged (because of possible view
1165 -- conversions), unless compiling for a VM where
1166 -- tags are implicit.
1168 if Present
(Comp_Type
)
1169 and then Is_Tagged_Type
(Comp_Type
)
1170 and then Tagged_Type_Expansion
1173 Full_Typ
: constant Entity_Id
:= Underlying_Type
(Comp_Type
);
1177 Make_OK_Assignment_Statement
(Loc
,
1179 Make_Selected_Component
(Loc
,
1180 Prefix
=> New_Copy_Tree
(Indexed_Comp
),
1183 (First_Tag_Component
(Full_Typ
), Loc
)),
1186 Unchecked_Convert_To
(RTE
(RE_Tag
),
1188 (Node
(First_Elmt
(Access_Disp_Table
(Full_Typ
))),
1195 -- Adjust and attach the component to the proper final list, which
1196 -- can be the controller of the outer record object or the final
1197 -- list associated with the scope.
1199 -- If the component is itself an array of controlled types, whose
1200 -- value is given by a sub-aggregate, then the attach calls have
1201 -- been generated when individual subcomponent are assigned, and
1202 -- must not be done again to prevent malformed finalization chains
1203 -- (see comments above, concerning the creation of a block to hold
1204 -- inner finalization actions).
1206 if Present
(Comp_Type
)
1207 and then Needs_Finalization
(Comp_Type
)
1208 and then not Is_Limited_Type
(Comp_Type
)
1210 (Is_Array_Type
(Comp_Type
)
1211 and then Is_Controlled
(Component_Type
(Comp_Type
))
1212 and then Nkind
(Expr
) = N_Aggregate
)
1216 Obj_Ref
=> New_Copy_Tree
(Indexed_Comp
),
1221 return Add_Loop_Actions
(L
);
1228 function Gen_Loop
(L
, H
: Node_Id
; Expr
: Node_Id
) return List_Id
is
1238 -- Index_Base'(L) .. Index_Base'(H)
1240 L_Iteration_Scheme
: Node_Id
;
1241 -- L_J in Index_Base'(L) .. Index_Base'(H)
1244 -- The statements to execute in the loop
1246 S
: constant List_Id
:= New_List
;
1247 -- List of statements
1250 -- Copy of expression tree, used for checking purposes
1253 -- If loop bounds define an empty range return the null statement
1255 if Empty_Range
(L
, H
) then
1256 Append_To
(S
, Make_Null_Statement
(Loc
));
1258 -- Ada 2005 (AI-287): Nothing else need to be done in case of
1259 -- default initialized component.
1265 -- The expression must be type-checked even though no component
1266 -- of the aggregate will have this value. This is done only for
1267 -- actual components of the array, not for subaggregates. Do
1268 -- the check on a copy, because the expression may be shared
1269 -- among several choices, some of which might be non-null.
1271 if Present
(Etype
(N
))
1272 and then Is_Array_Type
(Etype
(N
))
1273 and then No
(Next_Index
(Index
))
1275 Expander_Mode_Save_And_Set
(False);
1276 Tcopy
:= New_Copy_Tree
(Expr
);
1277 Set_Parent
(Tcopy
, N
);
1278 Analyze_And_Resolve
(Tcopy
, Component_Type
(Etype
(N
)));
1279 Expander_Mode_Restore
;
1285 -- If loop bounds are the same then generate an assignment
1287 elsif Equal
(L
, H
) then
1288 return Gen_Assign
(New_Copy_Tree
(L
), Expr
);
1290 -- If H - L <= 2 then generate a sequence of assignments when we are
1291 -- processing the bottom most aggregate and it contains scalar
1294 elsif No
(Next_Index
(Index
))
1295 and then Scalar_Comp
1296 and then Local_Compile_Time_Known_Value
(L
)
1297 and then Local_Compile_Time_Known_Value
(H
)
1298 and then Local_Expr_Value
(H
) - Local_Expr_Value
(L
) <= 2
1301 Append_List_To
(S
, Gen_Assign
(New_Copy_Tree
(L
), Expr
));
1302 Append_List_To
(S
, Gen_Assign
(Add
(1, To
=> L
), Expr
));
1304 if Local_Expr_Value
(H
) - Local_Expr_Value
(L
) = 2 then
1305 Append_List_To
(S
, Gen_Assign
(Add
(2, To
=> L
), Expr
));
1311 -- Otherwise construct the loop, starting with the loop index L_J
1313 L_J
:= Make_Temporary
(Loc
, 'J', L
);
1315 -- Construct "L .. H" in Index_Base. We use a qualified expression
1316 -- for the bound to convert to the index base, but we don't need
1317 -- to do that if we already have the base type at hand.
1319 if Etype
(L
) = Index_Base
then
1323 Make_Qualified_Expression
(Loc
,
1324 Subtype_Mark
=> Index_Base_Name
,
1328 if Etype
(H
) = Index_Base
then
1332 Make_Qualified_Expression
(Loc
,
1333 Subtype_Mark
=> Index_Base_Name
,
1342 -- Construct "for L_J in Index_Base range L .. H"
1344 L_Iteration_Scheme
:=
1345 Make_Iteration_Scheme
1347 Loop_Parameter_Specification
=>
1348 Make_Loop_Parameter_Specification
1350 Defining_Identifier
=> L_J
,
1351 Discrete_Subtype_Definition
=> L_Range
));
1353 -- Construct the statements to execute in the loop body
1355 L_Body
:= Gen_Assign
(New_Reference_To
(L_J
, Loc
), Expr
);
1357 -- Construct the final loop
1359 Append_To
(S
, Make_Implicit_Loop_Statement
1361 Identifier
=> Empty
,
1362 Iteration_Scheme
=> L_Iteration_Scheme
,
1363 Statements
=> L_Body
));
1365 -- A small optimization: if the aggregate is initialized with a box
1366 -- and the component type has no initialization procedure, remove the
1367 -- useless empty loop.
1369 if Nkind
(First
(S
)) = N_Loop_Statement
1370 and then Is_Empty_List
(Statements
(First
(S
)))
1372 return New_List
(Make_Null_Statement
(Loc
));
1382 -- The code built is
1384 -- W_J : Index_Base := L;
1385 -- while W_J < H loop
1386 -- W_J := Index_Base'Succ (W);
1390 function Gen_While
(L
, H
: Node_Id
; Expr
: Node_Id
) return List_Id
is
1394 -- W_J : Base_Type := L;
1396 W_Iteration_Scheme
: Node_Id
;
1399 W_Index_Succ
: Node_Id
;
1400 -- Index_Base'Succ (J)
1402 W_Increment
: Node_Id
;
1403 -- W_J := Index_Base'Succ (W)
1405 W_Body
: constant List_Id
:= New_List
;
1406 -- The statements to execute in the loop
1408 S
: constant List_Id
:= New_List
;
1409 -- list of statement
1412 -- If loop bounds define an empty range or are equal return null
1414 if Empty_Range
(L
, H
) or else Equal
(L
, H
) then
1415 Append_To
(S
, Make_Null_Statement
(Loc
));
1419 -- Build the decl of W_J
1421 W_J
:= Make_Temporary
(Loc
, 'J', L
);
1423 Make_Object_Declaration
1425 Defining_Identifier
=> W_J
,
1426 Object_Definition
=> Index_Base_Name
,
1429 -- Theoretically we should do a New_Copy_Tree (L) here, but we know
1430 -- that in this particular case L is a fresh Expr generated by
1431 -- Add which we are the only ones to use.
1433 Append_To
(S
, W_Decl
);
1435 -- Construct " while W_J < H"
1437 W_Iteration_Scheme
:=
1438 Make_Iteration_Scheme
1440 Condition
=> Make_Op_Lt
1442 Left_Opnd
=> New_Reference_To
(W_J
, Loc
),
1443 Right_Opnd
=> New_Copy_Tree
(H
)));
1445 -- Construct the statements to execute in the loop body
1448 Make_Attribute_Reference
1450 Prefix
=> Index_Base_Name
,
1451 Attribute_Name
=> Name_Succ
,
1452 Expressions
=> New_List
(New_Reference_To
(W_J
, Loc
)));
1455 Make_OK_Assignment_Statement
1457 Name
=> New_Reference_To
(W_J
, Loc
),
1458 Expression
=> W_Index_Succ
);
1460 Append_To
(W_Body
, W_Increment
);
1461 Append_List_To
(W_Body
,
1462 Gen_Assign
(New_Reference_To
(W_J
, Loc
), Expr
));
1464 -- Construct the final loop
1466 Append_To
(S
, Make_Implicit_Loop_Statement
1468 Identifier
=> Empty
,
1469 Iteration_Scheme
=> W_Iteration_Scheme
,
1470 Statements
=> W_Body
));
1475 ---------------------
1476 -- Index_Base_Name --
1477 ---------------------
1479 function Index_Base_Name
return Node_Id
is
1481 return New_Reference_To
(Index_Base
, Sloc
(N
));
1482 end Index_Base_Name
;
1484 ------------------------------------
1485 -- Local_Compile_Time_Known_Value --
1486 ------------------------------------
1488 function Local_Compile_Time_Known_Value
(E
: Node_Id
) return Boolean is
1490 return Compile_Time_Known_Value
(E
)
1492 (Nkind
(E
) = N_Attribute_Reference
1493 and then Attribute_Name
(E
) = Name_Val
1494 and then Compile_Time_Known_Value
(First
(Expressions
(E
))));
1495 end Local_Compile_Time_Known_Value
;
1497 ----------------------
1498 -- Local_Expr_Value --
1499 ----------------------
1501 function Local_Expr_Value
(E
: Node_Id
) return Uint
is
1503 if Compile_Time_Known_Value
(E
) then
1504 return Expr_Value
(E
);
1506 return Expr_Value
(First
(Expressions
(E
)));
1508 end Local_Expr_Value
;
1510 -- Build_Array_Aggr_Code Variables
1517 Others_Expr
: Node_Id
:= Empty
;
1518 Others_Box_Present
: Boolean := False;
1520 Aggr_L
: constant Node_Id
:= Low_Bound
(Aggregate_Bounds
(N
));
1521 Aggr_H
: constant Node_Id
:= High_Bound
(Aggregate_Bounds
(N
));
1522 -- The aggregate bounds of this specific sub-aggregate. Note that if
1523 -- the code generated by Build_Array_Aggr_Code is executed then these
1524 -- bounds are OK. Otherwise a Constraint_Error would have been raised.
1526 Aggr_Low
: constant Node_Id
:= Duplicate_Subexpr_No_Checks
(Aggr_L
);
1527 Aggr_High
: constant Node_Id
:= Duplicate_Subexpr_No_Checks
(Aggr_H
);
1528 -- After Duplicate_Subexpr these are side-effect free
1533 Nb_Choices
: Nat
:= 0;
1534 Table
: Case_Table_Type
(1 .. Number_Of_Choices
(N
));
1535 -- Used to sort all the different choice values
1538 -- Number of elements in the positional aggregate
1540 New_Code
: constant List_Id
:= New_List
;
1542 -- Start of processing for Build_Array_Aggr_Code
1545 -- First before we start, a special case. if we have a bit packed
1546 -- array represented as a modular type, then clear the value to
1547 -- zero first, to ensure that unused bits are properly cleared.
1552 and then Is_Bit_Packed_Array
(Typ
)
1553 and then Is_Modular_Integer_Type
(Packed_Array_Type
(Typ
))
1555 Append_To
(New_Code
,
1556 Make_Assignment_Statement
(Loc
,
1557 Name
=> New_Copy_Tree
(Into
),
1559 Unchecked_Convert_To
(Typ
,
1560 Make_Integer_Literal
(Loc
, Uint_0
))));
1563 -- If the component type contains tasks, we need to build a Master
1564 -- entity in the current scope, because it will be needed if build-
1565 -- in-place functions are called in the expanded code.
1567 if Nkind
(Parent
(N
)) = N_Object_Declaration
1568 and then Has_Task
(Typ
)
1570 Build_Master_Entity
(Defining_Identifier
(Parent
(N
)));
1573 -- STEP 1: Process component associations
1575 -- For those associations that may generate a loop, initialize
1576 -- Loop_Actions to collect inserted actions that may be crated.
1578 -- Skip this if no component associations
1580 if No
(Expressions
(N
)) then
1582 -- STEP 1 (a): Sort the discrete choices
1584 Assoc
:= First
(Component_Associations
(N
));
1585 while Present
(Assoc
) loop
1586 Choice
:= First
(Choices
(Assoc
));
1587 while Present
(Choice
) loop
1588 if Nkind
(Choice
) = N_Others_Choice
then
1589 Set_Loop_Actions
(Assoc
, New_List
);
1591 if Box_Present
(Assoc
) then
1592 Others_Box_Present
:= True;
1594 Others_Expr
:= Expression
(Assoc
);
1599 Get_Index_Bounds
(Choice
, Low
, High
);
1602 Set_Loop_Actions
(Assoc
, New_List
);
1605 Nb_Choices
:= Nb_Choices
+ 1;
1606 if Box_Present
(Assoc
) then
1607 Table
(Nb_Choices
) := (Choice_Lo
=> Low
,
1609 Choice_Node
=> Empty
);
1611 Table
(Nb_Choices
) := (Choice_Lo
=> Low
,
1613 Choice_Node
=> Expression
(Assoc
));
1621 -- If there is more than one set of choices these must be static
1622 -- and we can therefore sort them. Remember that Nb_Choices does not
1623 -- account for an others choice.
1625 if Nb_Choices
> 1 then
1626 Sort_Case_Table
(Table
);
1629 -- STEP 1 (b): take care of the whole set of discrete choices
1631 for J
in 1 .. Nb_Choices
loop
1632 Low
:= Table
(J
).Choice_Lo
;
1633 High
:= Table
(J
).Choice_Hi
;
1634 Expr
:= Table
(J
).Choice_Node
;
1635 Append_List
(Gen_Loop
(Low
, High
, Expr
), To
=> New_Code
);
1638 -- STEP 1 (c): generate the remaining loops to cover others choice
1639 -- We don't need to generate loops over empty gaps, but if there is
1640 -- a single empty range we must analyze the expression for semantics
1642 if Present
(Others_Expr
) or else Others_Box_Present
then
1644 First
: Boolean := True;
1647 for J
in 0 .. Nb_Choices
loop
1651 Low
:= Add
(1, To
=> Table
(J
).Choice_Hi
);
1654 if J
= Nb_Choices
then
1657 High
:= Add
(-1, To
=> Table
(J
+ 1).Choice_Lo
);
1660 -- If this is an expansion within an init proc, make
1661 -- sure that discriminant references are replaced by
1662 -- the corresponding discriminal.
1664 if Inside_Init_Proc
then
1665 if Is_Entity_Name
(Low
)
1666 and then Ekind
(Entity
(Low
)) = E_Discriminant
1668 Set_Entity
(Low
, Discriminal
(Entity
(Low
)));
1671 if Is_Entity_Name
(High
)
1672 and then Ekind
(Entity
(High
)) = E_Discriminant
1674 Set_Entity
(High
, Discriminal
(Entity
(High
)));
1679 or else not Empty_Range
(Low
, High
)
1683 (Gen_Loop
(Low
, High
, Others_Expr
), To
=> New_Code
);
1689 -- STEP 2: Process positional components
1692 -- STEP 2 (a): Generate the assignments for each positional element
1693 -- Note that here we have to use Aggr_L rather than Aggr_Low because
1694 -- Aggr_L is analyzed and Add wants an analyzed expression.
1696 Expr
:= First
(Expressions
(N
));
1698 while Present
(Expr
) loop
1699 Nb_Elements
:= Nb_Elements
+ 1;
1700 Append_List
(Gen_Assign
(Add
(Nb_Elements
, To
=> Aggr_L
), Expr
),
1705 -- STEP 2 (b): Generate final loop if an others choice is present
1706 -- Here Nb_Elements gives the offset of the last positional element.
1708 if Present
(Component_Associations
(N
)) then
1709 Assoc
:= Last
(Component_Associations
(N
));
1711 -- Ada 2005 (AI-287)
1713 if Box_Present
(Assoc
) then
1714 Append_List
(Gen_While
(Add
(Nb_Elements
, To
=> Aggr_L
),
1719 Expr
:= Expression
(Assoc
);
1721 Append_List
(Gen_While
(Add
(Nb_Elements
, To
=> Aggr_L
),
1730 end Build_Array_Aggr_Code
;
1732 ----------------------------
1733 -- Build_Record_Aggr_Code --
1734 ----------------------------
1736 function Build_Record_Aggr_Code
1739 Lhs
: Node_Id
) return List_Id
1741 Loc
: constant Source_Ptr
:= Sloc
(N
);
1742 L
: constant List_Id
:= New_List
;
1743 N_Typ
: constant Entity_Id
:= Etype
(N
);
1749 Comp_Type
: Entity_Id
;
1750 Selector
: Entity_Id
;
1751 Comp_Expr
: Node_Id
;
1754 -- If this is an internal aggregate, the External_Final_List is an
1755 -- expression for the controller record of the enclosing type.
1757 -- If the current aggregate has several controlled components, this
1758 -- expression will appear in several calls to attach to the finali-
1759 -- zation list, and it must not be shared.
1761 Ancestor_Is_Expression
: Boolean := False;
1762 Ancestor_Is_Subtype_Mark
: Boolean := False;
1764 Init_Typ
: Entity_Id
:= Empty
;
1766 Finalization_Done
: Boolean := False;
1767 -- True if Generate_Finalization_Actions has already been called; calls
1768 -- after the first do nothing.
1770 function Ancestor_Discriminant_Value
(Disc
: Entity_Id
) return Node_Id
;
1771 -- Returns the value that the given discriminant of an ancestor type
1772 -- should receive (in the absence of a conflict with the value provided
1773 -- by an ancestor part of an extension aggregate).
1775 procedure Check_Ancestor_Discriminants
(Anc_Typ
: Entity_Id
);
1776 -- Check that each of the discriminant values defined by the ancestor
1777 -- part of an extension aggregate match the corresponding values
1778 -- provided by either an association of the aggregate or by the
1779 -- constraint imposed by a parent type (RM95-4.3.2(8)).
1781 function Compatible_Int_Bounds
1782 (Agg_Bounds
: Node_Id
;
1783 Typ_Bounds
: Node_Id
) return Boolean;
1784 -- Return true if Agg_Bounds are equal or within Typ_Bounds. It is
1785 -- assumed that both bounds are integer ranges.
1787 procedure Generate_Finalization_Actions
;
1788 -- Deal with the various controlled type data structure initializations
1789 -- (but only if it hasn't been done already).
1791 function Get_Constraint_Association
(T
: Entity_Id
) return Node_Id
;
1792 -- Returns the first discriminant association in the constraint
1793 -- associated with T, if any, otherwise returns Empty.
1795 procedure Init_Hidden_Discriminants
(Typ
: Entity_Id
; List
: List_Id
);
1796 -- If Typ is derived, and constrains discriminants of the parent type,
1797 -- these discriminants are not components of the aggregate, and must be
1798 -- initialized. The assignments are appended to List.
1800 function Is_Int_Range_Bounds
(Bounds
: Node_Id
) return Boolean;
1801 -- Check whether Bounds is a range node and its lower and higher bounds
1802 -- are integers literals.
1804 ---------------------------------
1805 -- Ancestor_Discriminant_Value --
1806 ---------------------------------
1808 function Ancestor_Discriminant_Value
(Disc
: Entity_Id
) return Node_Id
is
1810 Assoc_Elmt
: Elmt_Id
;
1811 Aggr_Comp
: Entity_Id
;
1812 Corresp_Disc
: Entity_Id
;
1813 Current_Typ
: Entity_Id
:= Base_Type
(Typ
);
1814 Parent_Typ
: Entity_Id
;
1815 Parent_Disc
: Entity_Id
;
1816 Save_Assoc
: Node_Id
:= Empty
;
1819 -- First check any discriminant associations to see if any of them
1820 -- provide a value for the discriminant.
1822 if Present
(Discriminant_Specifications
(Parent
(Current_Typ
))) then
1823 Assoc
:= First
(Component_Associations
(N
));
1824 while Present
(Assoc
) loop
1825 Aggr_Comp
:= Entity
(First
(Choices
(Assoc
)));
1827 if Ekind
(Aggr_Comp
) = E_Discriminant
then
1828 Save_Assoc
:= Expression
(Assoc
);
1830 Corresp_Disc
:= Corresponding_Discriminant
(Aggr_Comp
);
1831 while Present
(Corresp_Disc
) loop
1833 -- If found a corresponding discriminant then return the
1834 -- value given in the aggregate. (Note: this is not
1835 -- correct in the presence of side effects. ???)
1837 if Disc
= Corresp_Disc
then
1838 return Duplicate_Subexpr
(Expression
(Assoc
));
1842 Corresponding_Discriminant
(Corresp_Disc
);
1850 -- No match found in aggregate, so chain up parent types to find
1851 -- a constraint that defines the value of the discriminant.
1853 Parent_Typ
:= Etype
(Current_Typ
);
1854 while Current_Typ
/= Parent_Typ
loop
1855 if Has_Discriminants
(Parent_Typ
)
1856 and then not Has_Unknown_Discriminants
(Parent_Typ
)
1858 Parent_Disc
:= First_Discriminant
(Parent_Typ
);
1860 -- We either get the association from the subtype indication
1861 -- of the type definition itself, or from the discriminant
1862 -- constraint associated with the type entity (which is
1863 -- preferable, but it's not always present ???)
1865 if Is_Empty_Elmt_List
(
1866 Discriminant_Constraint
(Current_Typ
))
1868 Assoc
:= Get_Constraint_Association
(Current_Typ
);
1869 Assoc_Elmt
:= No_Elmt
;
1872 First_Elmt
(Discriminant_Constraint
(Current_Typ
));
1873 Assoc
:= Node
(Assoc_Elmt
);
1876 -- Traverse the discriminants of the parent type looking
1877 -- for one that corresponds.
1879 while Present
(Parent_Disc
) and then Present
(Assoc
) loop
1880 Corresp_Disc
:= Parent_Disc
;
1881 while Present
(Corresp_Disc
)
1882 and then Disc
/= Corresp_Disc
1885 Corresponding_Discriminant
(Corresp_Disc
);
1888 if Disc
= Corresp_Disc
then
1889 if Nkind
(Assoc
) = N_Discriminant_Association
then
1890 Assoc
:= Expression
(Assoc
);
1893 -- If the located association directly denotes a
1894 -- discriminant, then use the value of a saved
1895 -- association of the aggregate. This is a kludge to
1896 -- handle certain cases involving multiple discriminants
1897 -- mapped to a single discriminant of a descendant. It's
1898 -- not clear how to locate the appropriate discriminant
1899 -- value for such cases. ???
1901 if Is_Entity_Name
(Assoc
)
1902 and then Ekind
(Entity
(Assoc
)) = E_Discriminant
1904 Assoc
:= Save_Assoc
;
1907 return Duplicate_Subexpr
(Assoc
);
1910 Next_Discriminant
(Parent_Disc
);
1912 if No
(Assoc_Elmt
) then
1915 Next_Elmt
(Assoc_Elmt
);
1916 if Present
(Assoc_Elmt
) then
1917 Assoc
:= Node
(Assoc_Elmt
);
1925 Current_Typ
:= Parent_Typ
;
1926 Parent_Typ
:= Etype
(Current_Typ
);
1929 -- In some cases there's no ancestor value to locate (such as
1930 -- when an ancestor part given by an expression defines the
1931 -- discriminant value).
1934 end Ancestor_Discriminant_Value
;
1936 ----------------------------------
1937 -- Check_Ancestor_Discriminants --
1938 ----------------------------------
1940 procedure Check_Ancestor_Discriminants
(Anc_Typ
: Entity_Id
) is
1942 Disc_Value
: Node_Id
;
1946 Discr
:= First_Discriminant
(Base_Type
(Anc_Typ
));
1947 while Present
(Discr
) loop
1948 Disc_Value
:= Ancestor_Discriminant_Value
(Discr
);
1950 if Present
(Disc_Value
) then
1951 Cond
:= Make_Op_Ne
(Loc
,
1953 Make_Selected_Component
(Loc
,
1954 Prefix
=> New_Copy_Tree
(Target
),
1955 Selector_Name
=> New_Occurrence_Of
(Discr
, Loc
)),
1956 Right_Opnd
=> Disc_Value
);
1959 Make_Raise_Constraint_Error
(Loc
,
1961 Reason
=> CE_Discriminant_Check_Failed
));
1964 Next_Discriminant
(Discr
);
1966 end Check_Ancestor_Discriminants
;
1968 ---------------------------
1969 -- Compatible_Int_Bounds --
1970 ---------------------------
1972 function Compatible_Int_Bounds
1973 (Agg_Bounds
: Node_Id
;
1974 Typ_Bounds
: Node_Id
) return Boolean
1976 Agg_Lo
: constant Uint
:= Intval
(Low_Bound
(Agg_Bounds
));
1977 Agg_Hi
: constant Uint
:= Intval
(High_Bound
(Agg_Bounds
));
1978 Typ_Lo
: constant Uint
:= Intval
(Low_Bound
(Typ_Bounds
));
1979 Typ_Hi
: constant Uint
:= Intval
(High_Bound
(Typ_Bounds
));
1981 return Typ_Lo
<= Agg_Lo
and then Agg_Hi
<= Typ_Hi
;
1982 end Compatible_Int_Bounds
;
1984 --------------------------------
1985 -- Get_Constraint_Association --
1986 --------------------------------
1988 function Get_Constraint_Association
(T
: Entity_Id
) return Node_Id
is
1995 -- Handle private types in instances
1998 and then Is_Private_Type
(Typ
)
1999 and then Present
(Full_View
(Typ
))
2001 Typ
:= Full_View
(Typ
);
2004 Indic
:= Subtype_Indication
(Type_Definition
(Parent
(Typ
)));
2006 -- ??? Also need to cover case of a type mark denoting a subtype
2009 if Nkind
(Indic
) = N_Subtype_Indication
2010 and then Present
(Constraint
(Indic
))
2012 return First
(Constraints
(Constraint
(Indic
)));
2016 end Get_Constraint_Association
;
2018 -------------------------------
2019 -- Init_Hidden_Discriminants --
2020 -------------------------------
2022 procedure Init_Hidden_Discriminants
(Typ
: Entity_Id
; List
: List_Id
) is
2024 Parent_Type
: Entity_Id
;
2026 Discr_Val
: Elmt_Id
;
2029 Btype
:= Base_Type
(Typ
);
2030 while Is_Derived_Type
(Btype
)
2031 and then Present
(Stored_Constraint
(Btype
))
2033 Parent_Type
:= Etype
(Btype
);
2035 Disc
:= First_Discriminant
(Parent_Type
);
2036 Discr_Val
:= First_Elmt
(Stored_Constraint
(Base_Type
(Typ
)));
2037 while Present
(Discr_Val
) loop
2039 -- Only those discriminants of the parent that are not
2040 -- renamed by discriminants of the derived type need to
2041 -- be added explicitly.
2043 if not Is_Entity_Name
(Node
(Discr_Val
))
2044 or else Ekind
(Entity
(Node
(Discr_Val
))) /= E_Discriminant
2047 Make_Selected_Component
(Loc
,
2048 Prefix
=> New_Copy_Tree
(Target
),
2049 Selector_Name
=> New_Occurrence_Of
(Disc
, Loc
));
2052 Make_OK_Assignment_Statement
(Loc
,
2054 Expression
=> New_Copy_Tree
(Node
(Discr_Val
)));
2056 Set_No_Ctrl_Actions
(Instr
);
2057 Append_To
(List
, Instr
);
2060 Next_Discriminant
(Disc
);
2061 Next_Elmt
(Discr_Val
);
2064 Btype
:= Base_Type
(Parent_Type
);
2066 end Init_Hidden_Discriminants
;
2068 -------------------------
2069 -- Is_Int_Range_Bounds --
2070 -------------------------
2072 function Is_Int_Range_Bounds
(Bounds
: Node_Id
) return Boolean is
2074 return Nkind
(Bounds
) = N_Range
2075 and then Nkind
(Low_Bound
(Bounds
)) = N_Integer_Literal
2076 and then Nkind
(High_Bound
(Bounds
)) = N_Integer_Literal
;
2077 end Is_Int_Range_Bounds
;
2079 -----------------------------------
2080 -- Generate_Finalization_Actions --
2081 -----------------------------------
2083 procedure Generate_Finalization_Actions
is
2085 -- Do the work only the first time this is called
2087 if Finalization_Done
then
2091 Finalization_Done
:= True;
2093 -- Determine the external finalization list. It is either the
2094 -- finalization list of the outer-scope or the one coming from
2095 -- an outer aggregate. When the target is not a temporary, the
2096 -- proper scope is the scope of the target rather than the
2097 -- potentially transient current scope.
2099 if Is_Controlled
(Typ
)
2100 and then Ancestor_Is_Subtype_Mark
2102 Ref
:= Convert_To
(Init_Typ
, New_Copy_Tree
(Target
));
2103 Set_Assignment_OK
(Ref
);
2106 Make_Procedure_Call_Statement
(Loc
,
2109 (Find_Prim_Op
(Init_Typ
, Name_Initialize
), Loc
),
2110 Parameter_Associations
=> New_List
(New_Copy_Tree
(Ref
))));
2112 end Generate_Finalization_Actions
;
2114 function Rewrite_Discriminant
(Expr
: Node_Id
) return Traverse_Result
;
2115 -- If default expression of a component mentions a discriminant of the
2116 -- type, it must be rewritten as the discriminant of the target object.
2118 function Replace_Type
(Expr
: Node_Id
) return Traverse_Result
;
2119 -- If the aggregate contains a self-reference, traverse each expression
2120 -- to replace a possible self-reference with a reference to the proper
2121 -- component of the target of the assignment.
2123 --------------------------
2124 -- Rewrite_Discriminant --
2125 --------------------------
2127 function Rewrite_Discriminant
(Expr
: Node_Id
) return Traverse_Result
is
2129 if Is_Entity_Name
(Expr
)
2130 and then Present
(Entity
(Expr
))
2131 and then Ekind
(Entity
(Expr
)) = E_In_Parameter
2132 and then Present
(Discriminal_Link
(Entity
(Expr
)))
2133 and then Scope
(Discriminal_Link
(Entity
(Expr
)))
2134 = Base_Type
(Etype
(N
))
2137 Make_Selected_Component
(Loc
,
2138 Prefix
=> New_Copy_Tree
(Lhs
),
2139 Selector_Name
=> Make_Identifier
(Loc
, Chars
(Expr
))));
2142 end Rewrite_Discriminant
;
2148 function Replace_Type
(Expr
: Node_Id
) return Traverse_Result
is
2150 -- Note regarding the Root_Type test below: Aggregate components for
2151 -- self-referential types include attribute references to the current
2152 -- instance, of the form: Typ'access, etc.. These references are
2153 -- rewritten as references to the target of the aggregate: the
2154 -- left-hand side of an assignment, the entity in a declaration,
2155 -- or a temporary. Without this test, we would improperly extended
2156 -- this rewriting to attribute references whose prefix was not the
2157 -- type of the aggregate.
2159 if Nkind
(Expr
) = N_Attribute_Reference
2160 and then Is_Entity_Name
(Prefix
(Expr
))
2161 and then Is_Type
(Entity
(Prefix
(Expr
)))
2162 and then Root_Type
(Etype
(N
)) = Root_Type
(Entity
(Prefix
(Expr
)))
2164 if Is_Entity_Name
(Lhs
) then
2165 Rewrite
(Prefix
(Expr
),
2166 New_Occurrence_Of
(Entity
(Lhs
), Loc
));
2168 elsif Nkind
(Lhs
) = N_Selected_Component
then
2170 Make_Attribute_Reference
(Loc
,
2171 Attribute_Name
=> Name_Unrestricted_Access
,
2172 Prefix
=> New_Copy_Tree
(Lhs
)));
2173 Set_Analyzed
(Parent
(Expr
), False);
2177 Make_Attribute_Reference
(Loc
,
2178 Attribute_Name
=> Name_Unrestricted_Access
,
2179 Prefix
=> New_Copy_Tree
(Lhs
)));
2180 Set_Analyzed
(Parent
(Expr
), False);
2187 procedure Replace_Self_Reference
is
2188 new Traverse_Proc
(Replace_Type
);
2190 procedure Replace_Discriminants
is
2191 new Traverse_Proc
(Rewrite_Discriminant
);
2193 -- Start of processing for Build_Record_Aggr_Code
2196 if Has_Self_Reference
(N
) then
2197 Replace_Self_Reference
(N
);
2200 -- If the target of the aggregate is class-wide, we must convert it
2201 -- to the actual type of the aggregate, so that the proper components
2202 -- are visible. We know already that the types are compatible.
2204 if Present
(Etype
(Lhs
))
2205 and then Is_Class_Wide_Type
(Etype
(Lhs
))
2207 Target
:= Unchecked_Convert_To
(Typ
, Lhs
);
2212 -- Deal with the ancestor part of extension aggregates or with the
2213 -- discriminants of the root type.
2215 if Nkind
(N
) = N_Extension_Aggregate
then
2217 Ancestor
: constant Node_Id
:= Ancestor_Part
(N
);
2221 -- If the ancestor part is a subtype mark "T", we generate
2223 -- init-proc (T (tmp)); if T is constrained and
2224 -- init-proc (S (tmp)); where S applies an appropriate
2225 -- constraint if T is unconstrained
2227 if Is_Entity_Name
(Ancestor
)
2228 and then Is_Type
(Entity
(Ancestor
))
2230 Ancestor_Is_Subtype_Mark
:= True;
2232 if Is_Constrained
(Entity
(Ancestor
)) then
2233 Init_Typ
:= Entity
(Ancestor
);
2235 -- For an ancestor part given by an unconstrained type mark,
2236 -- create a subtype constrained by appropriate corresponding
2237 -- discriminant values coming from either associations of the
2238 -- aggregate or a constraint on a parent type. The subtype will
2239 -- be used to generate the correct default value for the
2242 elsif Has_Discriminants
(Entity
(Ancestor
)) then
2244 Anc_Typ
: constant Entity_Id
:= Entity
(Ancestor
);
2245 Anc_Constr
: constant List_Id
:= New_List
;
2246 Discrim
: Entity_Id
;
2247 Disc_Value
: Node_Id
;
2248 New_Indic
: Node_Id
;
2249 Subt_Decl
: Node_Id
;
2252 Discrim
:= First_Discriminant
(Anc_Typ
);
2253 while Present
(Discrim
) loop
2254 Disc_Value
:= Ancestor_Discriminant_Value
(Discrim
);
2255 Append_To
(Anc_Constr
, Disc_Value
);
2256 Next_Discriminant
(Discrim
);
2260 Make_Subtype_Indication
(Loc
,
2261 Subtype_Mark
=> New_Occurrence_Of
(Anc_Typ
, Loc
),
2263 Make_Index_Or_Discriminant_Constraint
(Loc
,
2264 Constraints
=> Anc_Constr
));
2266 Init_Typ
:= Create_Itype
(Ekind
(Anc_Typ
), N
);
2269 Make_Subtype_Declaration
(Loc
,
2270 Defining_Identifier
=> Init_Typ
,
2271 Subtype_Indication
=> New_Indic
);
2273 -- Itypes must be analyzed with checks off Declaration
2274 -- must have a parent for proper handling of subsidiary
2277 Set_Parent
(Subt_Decl
, N
);
2278 Analyze
(Subt_Decl
, Suppress
=> All_Checks
);
2282 Ref
:= Convert_To
(Init_Typ
, New_Copy_Tree
(Target
));
2283 Set_Assignment_OK
(Ref
);
2285 if not Is_Interface
(Init_Typ
) then
2287 Build_Initialization_Call
(Loc
,
2290 In_Init_Proc
=> Within_Init_Proc
,
2291 With_Default_Init
=> Has_Default_Init_Comps
(N
)
2293 Has_Task
(Base_Type
(Init_Typ
))));
2295 if Is_Constrained
(Entity
(Ancestor
))
2296 and then Has_Discriminants
(Entity
(Ancestor
))
2298 Check_Ancestor_Discriminants
(Entity
(Ancestor
));
2302 -- Handle calls to C++ constructors
2304 elsif Is_CPP_Constructor_Call
(Ancestor
) then
2305 Init_Typ
:= Etype
(Ancestor
);
2306 Ref
:= Convert_To
(Init_Typ
, New_Copy_Tree
(Target
));
2307 Set_Assignment_OK
(Ref
);
2310 Build_Initialization_Call
(Loc
,
2313 In_Init_Proc
=> Within_Init_Proc
,
2314 With_Default_Init
=> Has_Default_Init_Comps
(N
),
2315 Constructor_Ref
=> Ancestor
));
2317 -- Ada 2005 (AI-287): If the ancestor part is an aggregate of
2318 -- limited type, a recursive call expands the ancestor. Note that
2319 -- in the limited case, the ancestor part must be either a
2320 -- function call (possibly qualified, or wrapped in an unchecked
2321 -- conversion) or aggregate (definitely qualified).
2322 -- The ancestor part can also be a function call (that may be
2323 -- transformed into an explicit dereference) or a qualification
2326 elsif Is_Limited_Type
(Etype
(Ancestor
))
2327 and then Nkind_In
(Unqualify
(Ancestor
), N_Aggregate
,
2328 N_Extension_Aggregate
)
2330 Ancestor_Is_Expression
:= True;
2332 -- Set up finalization data for enclosing record, because
2333 -- controlled subcomponents of the ancestor part will be
2336 Generate_Finalization_Actions
;
2339 Build_Record_Aggr_Code
2340 (N
=> Unqualify
(Ancestor
),
2341 Typ
=> Etype
(Unqualify
(Ancestor
)),
2344 -- If the ancestor part is an expression "E", we generate
2348 -- In Ada 2005, this includes the case of a (possibly qualified)
2349 -- limited function call. The assignment will turn into a
2350 -- build-in-place function call (for further details, see
2351 -- Make_Build_In_Place_Call_In_Assignment).
2354 Ancestor_Is_Expression
:= True;
2355 Init_Typ
:= Etype
(Ancestor
);
2357 -- If the ancestor part is an aggregate, force its full
2358 -- expansion, which was delayed.
2360 if Nkind_In
(Unqualify
(Ancestor
), N_Aggregate
,
2361 N_Extension_Aggregate
)
2363 Set_Analyzed
(Ancestor
, False);
2364 Set_Analyzed
(Expression
(Ancestor
), False);
2367 Ref
:= Convert_To
(Init_Typ
, New_Copy_Tree
(Target
));
2368 Set_Assignment_OK
(Ref
);
2370 -- Make the assignment without usual controlled actions since
2371 -- we only want the post adjust but not the pre finalize here
2372 -- Add manual adjust when necessary.
2374 Assign
:= New_List
(
2375 Make_OK_Assignment_Statement
(Loc
,
2377 Expression
=> Ancestor
));
2378 Set_No_Ctrl_Actions
(First
(Assign
));
2380 -- Assign the tag now to make sure that the dispatching call in
2381 -- the subsequent deep_adjust works properly (unless VM_Target,
2382 -- where tags are implicit).
2384 if Tagged_Type_Expansion
then
2386 Make_OK_Assignment_Statement
(Loc
,
2388 Make_Selected_Component
(Loc
,
2389 Prefix
=> New_Copy_Tree
(Target
),
2392 (First_Tag_Component
(Base_Type
(Typ
)), Loc
)),
2395 Unchecked_Convert_To
(RTE
(RE_Tag
),
2398 (Access_Disp_Table
(Base_Type
(Typ
)))),
2401 Set_Assignment_OK
(Name
(Instr
));
2402 Append_To
(Assign
, Instr
);
2404 -- Ada 2005 (AI-251): If tagged type has progenitors we must
2405 -- also initialize tags of the secondary dispatch tables.
2407 if Has_Interfaces
(Base_Type
(Typ
)) then
2409 (Typ
=> Base_Type
(Typ
),
2411 Stmts_List
=> Assign
);
2415 -- Call Adjust manually
2417 if Needs_Finalization
(Etype
(Ancestor
))
2418 and then not Is_Limited_Type
(Etype
(Ancestor
))
2422 Obj_Ref
=> New_Copy_Tree
(Ref
),
2423 Typ
=> Etype
(Ancestor
)));
2427 Make_Unsuppress_Block
(Loc
, Name_Discriminant_Check
, Assign
));
2429 if Has_Discriminants
(Init_Typ
) then
2430 Check_Ancestor_Discriminants
(Init_Typ
);
2435 -- Generate assignments of hidden assignments. If the base type is an
2436 -- unchecked union, the discriminants are unknown to the back-end and
2437 -- absent from a value of the type, so assignments for them are not
2440 if Has_Discriminants
(Typ
)
2441 and then not Is_Unchecked_Union
(Base_Type
(Typ
))
2443 Init_Hidden_Discriminants
(Typ
, L
);
2446 -- Normal case (not an extension aggregate)
2449 -- Generate the discriminant expressions, component by component.
2450 -- If the base type is an unchecked union, the discriminants are
2451 -- unknown to the back-end and absent from a value of the type, so
2452 -- assignments for them are not emitted.
2454 if Has_Discriminants
(Typ
)
2455 and then not Is_Unchecked_Union
(Base_Type
(Typ
))
2457 Init_Hidden_Discriminants
(Typ
, L
);
2459 -- Generate discriminant init values for the visible discriminants
2462 Discriminant
: Entity_Id
;
2463 Discriminant_Value
: Node_Id
;
2466 Discriminant
:= First_Stored_Discriminant
(Typ
);
2467 while Present
(Discriminant
) loop
2469 Make_Selected_Component
(Loc
,
2470 Prefix
=> New_Copy_Tree
(Target
),
2471 Selector_Name
=> New_Occurrence_Of
(Discriminant
, Loc
));
2473 Discriminant_Value
:=
2474 Get_Discriminant_Value
(
2477 Discriminant_Constraint
(N_Typ
));
2480 Make_OK_Assignment_Statement
(Loc
,
2482 Expression
=> New_Copy_Tree
(Discriminant_Value
));
2484 Set_No_Ctrl_Actions
(Instr
);
2485 Append_To
(L
, Instr
);
2487 Next_Stored_Discriminant
(Discriminant
);
2493 -- For CPP types we generate an implicit call to the C++ default
2494 -- constructor to ensure the proper initialization of the _Tag
2497 if Is_CPP_Class
(Root_Type
(Typ
))
2498 and then CPP_Num_Prims
(Typ
) > 0
2500 Invoke_Constructor
: declare
2501 CPP_Parent
: constant Entity_Id
:=
2502 Enclosing_CPP_Parent
(Typ
);
2504 procedure Invoke_IC_Proc
(T
: Entity_Id
);
2505 -- Recursive routine used to climb to parents. Required because
2506 -- parents must be initialized before descendants to ensure
2507 -- propagation of inherited C++ slots.
2509 --------------------
2510 -- Invoke_IC_Proc --
2511 --------------------
2513 procedure Invoke_IC_Proc
(T
: Entity_Id
) is
2515 -- Avoid generating extra calls. Initialization required
2516 -- only for types defined from the level of derivation of
2517 -- type of the constructor and the type of the aggregate.
2519 if T
= CPP_Parent
then
2523 Invoke_IC_Proc
(Etype
(T
));
2525 -- Generate call to the IC routine
2527 if Present
(CPP_Init_Proc
(T
)) then
2529 Make_Procedure_Call_Statement
(Loc
,
2530 New_Reference_To
(CPP_Init_Proc
(T
), Loc
)));
2534 -- Start of processing for Invoke_Constructor
2537 -- Implicit invocation of the C++ constructor
2539 if Nkind
(N
) = N_Aggregate
then
2541 Make_Procedure_Call_Statement
(Loc
,
2544 (Base_Init_Proc
(CPP_Parent
), Loc
),
2545 Parameter_Associations
=> New_List
(
2546 Unchecked_Convert_To
(CPP_Parent
,
2547 New_Copy_Tree
(Lhs
)))));
2550 Invoke_IC_Proc
(Typ
);
2551 end Invoke_Constructor
;
2554 -- Generate the assignments, component by component
2556 -- tmp.comp1 := Expr1_From_Aggr;
2557 -- tmp.comp2 := Expr2_From_Aggr;
2560 Comp
:= First
(Component_Associations
(N
));
2561 while Present
(Comp
) loop
2562 Selector
:= Entity
(First
(Choices
(Comp
)));
2566 if Is_CPP_Constructor_Call
(Expression
(Comp
)) then
2568 Build_Initialization_Call
(Loc
,
2569 Id_Ref
=> Make_Selected_Component
(Loc
,
2570 Prefix
=> New_Copy_Tree
(Target
),
2572 New_Occurrence_Of
(Selector
, Loc
)),
2573 Typ
=> Etype
(Selector
),
2575 With_Default_Init
=> True,
2576 Constructor_Ref
=> Expression
(Comp
)));
2578 -- Ada 2005 (AI-287): For each default-initialized component generate
2579 -- a call to the corresponding IP subprogram if available.
2581 elsif Box_Present
(Comp
)
2582 and then Has_Non_Null_Base_Init_Proc
(Etype
(Selector
))
2584 if Ekind
(Selector
) /= E_Discriminant
then
2585 Generate_Finalization_Actions
;
2588 -- Ada 2005 (AI-287): If the component type has tasks then
2589 -- generate the activation chain and master entities (except
2590 -- in case of an allocator because in that case these entities
2591 -- are generated by Build_Task_Allocate_Block_With_Init_Stmts).
2594 Ctype
: constant Entity_Id
:= Etype
(Selector
);
2595 Inside_Allocator
: Boolean := False;
2596 P
: Node_Id
:= Parent
(N
);
2599 if Is_Task_Type
(Ctype
) or else Has_Task
(Ctype
) then
2600 while Present
(P
) loop
2601 if Nkind
(P
) = N_Allocator
then
2602 Inside_Allocator
:= True;
2609 if not Inside_Init_Proc
and not Inside_Allocator
then
2610 Build_Activation_Chain_Entity
(N
);
2616 Build_Initialization_Call
(Loc
,
2617 Id_Ref
=> Make_Selected_Component
(Loc
,
2618 Prefix
=> New_Copy_Tree
(Target
),
2620 New_Occurrence_Of
(Selector
, Loc
)),
2621 Typ
=> Etype
(Selector
),
2623 With_Default_Init
=> True));
2625 -- Prepare for component assignment
2627 elsif Ekind
(Selector
) /= E_Discriminant
2628 or else Nkind
(N
) = N_Extension_Aggregate
2630 -- All the discriminants have now been assigned
2632 -- This is now a good moment to initialize and attach all the
2633 -- controllers. Their position may depend on the discriminants.
2635 if Ekind
(Selector
) /= E_Discriminant
then
2636 Generate_Finalization_Actions
;
2639 Comp_Type
:= Underlying_Type
(Etype
(Selector
));
2641 Make_Selected_Component
(Loc
,
2642 Prefix
=> New_Copy_Tree
(Target
),
2643 Selector_Name
=> New_Occurrence_Of
(Selector
, Loc
));
2645 if Nkind
(Expression
(Comp
)) = N_Qualified_Expression
then
2646 Expr_Q
:= Expression
(Expression
(Comp
));
2648 Expr_Q
:= Expression
(Comp
);
2651 -- Now either create the assignment or generate the code for the
2652 -- inner aggregate top-down.
2654 if Is_Delayed_Aggregate
(Expr_Q
) then
2656 -- We have the following case of aggregate nesting inside
2657 -- an object declaration:
2659 -- type Arr_Typ is array (Integer range <>) of ...;
2661 -- type Rec_Typ (...) is record
2662 -- Obj_Arr_Typ : Arr_Typ (A .. B);
2665 -- Obj_Rec_Typ : Rec_Typ := (...,
2666 -- Obj_Arr_Typ => (X => (...), Y => (...)));
2668 -- The length of the ranges of the aggregate and Obj_Add_Typ
2669 -- are equal (B - A = Y - X), but they do not coincide (X /=
2670 -- A and B /= Y). This case requires array sliding which is
2671 -- performed in the following manner:
2673 -- subtype Arr_Sub is Arr_Typ (X .. Y);
2675 -- Temp (X) := (...);
2677 -- Temp (Y) := (...);
2678 -- Obj_Rec_Typ.Obj_Arr_Typ := Temp;
2680 if Ekind
(Comp_Type
) = E_Array_Subtype
2681 and then Is_Int_Range_Bounds
(Aggregate_Bounds
(Expr_Q
))
2682 and then Is_Int_Range_Bounds
(First_Index
(Comp_Type
))
2684 Compatible_Int_Bounds
2685 (Agg_Bounds
=> Aggregate_Bounds
(Expr_Q
),
2686 Typ_Bounds
=> First_Index
(Comp_Type
))
2688 -- Create the array subtype with bounds equal to those of
2689 -- the corresponding aggregate.
2692 SubE
: constant Entity_Id
:= Make_Temporary
(Loc
, 'T');
2694 SubD
: constant Node_Id
:=
2695 Make_Subtype_Declaration
(Loc
,
2696 Defining_Identifier
=> SubE
,
2697 Subtype_Indication
=>
2698 Make_Subtype_Indication
(Loc
,
2701 (Etype
(Comp_Type
), Loc
),
2703 Make_Index_Or_Discriminant_Constraint
2705 Constraints
=> New_List
(
2707 (Aggregate_Bounds
(Expr_Q
))))));
2709 -- Create a temporary array of the above subtype which
2710 -- will be used to capture the aggregate assignments.
2712 TmpE
: constant Entity_Id
:= Make_Temporary
(Loc
, 'A', N
);
2714 TmpD
: constant Node_Id
:=
2715 Make_Object_Declaration
(Loc
,
2716 Defining_Identifier
=> TmpE
,
2717 Object_Definition
=>
2718 New_Reference_To
(SubE
, Loc
));
2721 Set_No_Initialization
(TmpD
);
2722 Append_To
(L
, SubD
);
2723 Append_To
(L
, TmpD
);
2725 -- Expand aggregate into assignments to the temp array
2728 Late_Expansion
(Expr_Q
, Comp_Type
,
2729 New_Reference_To
(TmpE
, Loc
)));
2734 Make_Assignment_Statement
(Loc
,
2735 Name
=> New_Copy_Tree
(Comp_Expr
),
2736 Expression
=> New_Reference_To
(TmpE
, Loc
)));
2739 -- Normal case (sliding not required)
2743 Late_Expansion
(Expr_Q
, Comp_Type
, Comp_Expr
));
2746 -- Expr_Q is not delayed aggregate
2749 if Has_Discriminants
(Typ
) then
2750 Replace_Discriminants
(Expr_Q
);
2754 Make_OK_Assignment_Statement
(Loc
,
2756 Expression
=> Expr_Q
);
2758 Set_No_Ctrl_Actions
(Instr
);
2759 Append_To
(L
, Instr
);
2761 -- Adjust the tag if tagged (because of possible view
2762 -- conversions), unless compiling for a VM where tags are
2765 -- tmp.comp._tag := comp_typ'tag;
2767 if Is_Tagged_Type
(Comp_Type
)
2768 and then Tagged_Type_Expansion
2771 Make_OK_Assignment_Statement
(Loc
,
2773 Make_Selected_Component
(Loc
,
2774 Prefix
=> New_Copy_Tree
(Comp_Expr
),
2777 (First_Tag_Component
(Comp_Type
), Loc
)),
2780 Unchecked_Convert_To
(RTE
(RE_Tag
),
2782 (Node
(First_Elmt
(Access_Disp_Table
(Comp_Type
))),
2785 Append_To
(L
, Instr
);
2789 -- Adjust (tmp.comp);
2791 if Needs_Finalization
(Comp_Type
)
2792 and then not Is_Limited_Type
(Comp_Type
)
2796 Obj_Ref
=> New_Copy_Tree
(Comp_Expr
),
2803 elsif Ekind
(Selector
) = E_Discriminant
2804 and then Nkind
(N
) /= N_Extension_Aggregate
2805 and then Nkind
(Parent
(N
)) = N_Component_Association
2806 and then Is_Constrained
(Typ
)
2808 -- We must check that the discriminant value imposed by the
2809 -- context is the same as the value given in the subaggregate,
2810 -- because after the expansion into assignments there is no
2811 -- record on which to perform a regular discriminant check.
2818 D_Val
:= First_Elmt
(Discriminant_Constraint
(Typ
));
2819 Disc
:= First_Discriminant
(Typ
);
2820 while Chars
(Disc
) /= Chars
(Selector
) loop
2821 Next_Discriminant
(Disc
);
2825 pragma Assert
(Present
(D_Val
));
2827 -- This check cannot performed for components that are
2828 -- constrained by a current instance, because this is not a
2829 -- value that can be compared with the actual constraint.
2831 if Nkind
(Node
(D_Val
)) /= N_Attribute_Reference
2832 or else not Is_Entity_Name
(Prefix
(Node
(D_Val
)))
2833 or else not Is_Type
(Entity
(Prefix
(Node
(D_Val
))))
2836 Make_Raise_Constraint_Error
(Loc
,
2839 Left_Opnd
=> New_Copy_Tree
(Node
(D_Val
)),
2840 Right_Opnd
=> Expression
(Comp
)),
2841 Reason
=> CE_Discriminant_Check_Failed
));
2844 -- Find self-reference in previous discriminant assignment,
2845 -- and replace with proper expression.
2852 while Present
(Ass
) loop
2853 if Nkind
(Ass
) = N_Assignment_Statement
2854 and then Nkind
(Name
(Ass
)) = N_Selected_Component
2855 and then Chars
(Selector_Name
(Name
(Ass
))) =
2859 (Ass
, New_Copy_Tree
(Expression
(Comp
)));
2872 -- If the type is tagged, the tag needs to be initialized (unless
2873 -- compiling for the Java VM where tags are implicit). It is done
2874 -- late in the initialization process because in some cases, we call
2875 -- the init proc of an ancestor which will not leave out the right tag
2877 if Ancestor_Is_Expression
then
2880 -- For CPP types we generated a call to the C++ default constructor
2881 -- before the components have been initialized to ensure the proper
2882 -- initialization of the _Tag component (see above).
2884 elsif Is_CPP_Class
(Typ
) then
2887 elsif Is_Tagged_Type
(Typ
) and then Tagged_Type_Expansion
then
2889 Make_OK_Assignment_Statement
(Loc
,
2891 Make_Selected_Component
(Loc
,
2892 Prefix
=> New_Copy_Tree
(Target
),
2895 (First_Tag_Component
(Base_Type
(Typ
)), Loc
)),
2898 Unchecked_Convert_To
(RTE
(RE_Tag
),
2900 (Node
(First_Elmt
(Access_Disp_Table
(Base_Type
(Typ
)))),
2903 Append_To
(L
, Instr
);
2905 -- Ada 2005 (AI-251): If the tagged type has been derived from
2906 -- abstract interfaces we must also initialize the tags of the
2907 -- secondary dispatch tables.
2909 if Has_Interfaces
(Base_Type
(Typ
)) then
2911 (Typ
=> Base_Type
(Typ
),
2917 -- If the controllers have not been initialized yet (by lack of non-
2918 -- discriminant components), let's do it now.
2920 Generate_Finalization_Actions
;
2923 end Build_Record_Aggr_Code
;
2925 -------------------------------
2926 -- Convert_Aggr_In_Allocator --
2927 -------------------------------
2929 procedure Convert_Aggr_In_Allocator
2934 Loc
: constant Source_Ptr
:= Sloc
(Aggr
);
2935 Typ
: constant Entity_Id
:= Etype
(Aggr
);
2936 Temp
: constant Entity_Id
:= Defining_Identifier
(Decl
);
2938 Occ
: constant Node_Id
:=
2939 Unchecked_Convert_To
(Typ
,
2940 Make_Explicit_Dereference
(Loc
,
2941 New_Reference_To
(Temp
, Loc
)));
2944 if Is_Array_Type
(Typ
) then
2945 Convert_Array_Aggr_In_Allocator
(Decl
, Aggr
, Occ
);
2947 elsif Has_Default_Init_Comps
(Aggr
) then
2949 L
: constant List_Id
:= New_List
;
2950 Init_Stmts
: List_Id
;
2953 Init_Stmts
:= Late_Expansion
(Aggr
, Typ
, Occ
);
2955 if Has_Task
(Typ
) then
2956 Build_Task_Allocate_Block_With_Init_Stmts
(L
, Aggr
, Init_Stmts
);
2957 Insert_Actions
(Alloc
, L
);
2959 Insert_Actions
(Alloc
, Init_Stmts
);
2964 Insert_Actions
(Alloc
, Late_Expansion
(Aggr
, Typ
, Occ
));
2966 end Convert_Aggr_In_Allocator
;
2968 --------------------------------
2969 -- Convert_Aggr_In_Assignment --
2970 --------------------------------
2972 procedure Convert_Aggr_In_Assignment
(N
: Node_Id
) is
2973 Aggr
: Node_Id
:= Expression
(N
);
2974 Typ
: constant Entity_Id
:= Etype
(Aggr
);
2975 Occ
: constant Node_Id
:= New_Copy_Tree
(Name
(N
));
2978 if Nkind
(Aggr
) = N_Qualified_Expression
then
2979 Aggr
:= Expression
(Aggr
);
2982 Insert_Actions_After
(N
, Late_Expansion
(Aggr
, Typ
, Occ
));
2983 end Convert_Aggr_In_Assignment
;
2985 ---------------------------------
2986 -- Convert_Aggr_In_Object_Decl --
2987 ---------------------------------
2989 procedure Convert_Aggr_In_Object_Decl
(N
: Node_Id
) is
2990 Obj
: constant Entity_Id
:= Defining_Identifier
(N
);
2991 Aggr
: Node_Id
:= Expression
(N
);
2992 Loc
: constant Source_Ptr
:= Sloc
(Aggr
);
2993 Typ
: constant Entity_Id
:= Etype
(Aggr
);
2994 Occ
: constant Node_Id
:= New_Occurrence_Of
(Obj
, Loc
);
2996 function Discriminants_Ok
return Boolean;
2997 -- If the object type is constrained, the discriminants in the
2998 -- aggregate must be checked against the discriminants of the subtype.
2999 -- This cannot be done using Apply_Discriminant_Checks because after
3000 -- expansion there is no aggregate left to check.
3002 ----------------------
3003 -- Discriminants_Ok --
3004 ----------------------
3006 function Discriminants_Ok
return Boolean is
3007 Cond
: Node_Id
:= Empty
;
3016 D
:= First_Discriminant
(Typ
);
3017 Disc1
:= First_Elmt
(Discriminant_Constraint
(Typ
));
3018 Disc2
:= First_Elmt
(Discriminant_Constraint
(Etype
(Obj
)));
3019 while Present
(Disc1
) and then Present
(Disc2
) loop
3020 Val1
:= Node
(Disc1
);
3021 Val2
:= Node
(Disc2
);
3023 if not Is_OK_Static_Expression
(Val1
)
3024 or else not Is_OK_Static_Expression
(Val2
)
3026 Check
:= Make_Op_Ne
(Loc
,
3027 Left_Opnd
=> Duplicate_Subexpr
(Val1
),
3028 Right_Opnd
=> Duplicate_Subexpr
(Val2
));
3034 Cond
:= Make_Or_Else
(Loc
,
3036 Right_Opnd
=> Check
);
3039 elsif Expr_Value
(Val1
) /= Expr_Value
(Val2
) then
3040 Apply_Compile_Time_Constraint_Error
(Aggr
,
3041 Msg
=> "incorrect value for discriminant&?",
3042 Reason
=> CE_Discriminant_Check_Failed
,
3047 Next_Discriminant
(D
);
3052 -- If any discriminant constraint is non-static, emit a check
3054 if Present
(Cond
) then
3056 Make_Raise_Constraint_Error
(Loc
,
3058 Reason
=> CE_Discriminant_Check_Failed
));
3062 end Discriminants_Ok
;
3064 -- Start of processing for Convert_Aggr_In_Object_Decl
3067 Set_Assignment_OK
(Occ
);
3069 if Nkind
(Aggr
) = N_Qualified_Expression
then
3070 Aggr
:= Expression
(Aggr
);
3073 if Has_Discriminants
(Typ
)
3074 and then Typ
/= Etype
(Obj
)
3075 and then Is_Constrained
(Etype
(Obj
))
3076 and then not Discriminants_Ok
3081 -- If the context is an extended return statement, it has its own
3082 -- finalization machinery (i.e. works like a transient scope) and
3083 -- we do not want to create an additional one, because objects on
3084 -- the finalization list of the return must be moved to the caller's
3085 -- finalization list to complete the return.
3087 -- However, if the aggregate is limited, it is built in place, and the
3088 -- controlled components are not assigned to intermediate temporaries
3089 -- so there is no need for a transient scope in this case either.
3091 if Requires_Transient_Scope
(Typ
)
3092 and then Ekind
(Current_Scope
) /= E_Return_Statement
3093 and then not Is_Limited_Type
(Typ
)
3095 Establish_Transient_Scope
3098 Is_Controlled
(Typ
) or else Has_Controlled_Component
(Typ
));
3101 Insert_Actions_After
(N
, Late_Expansion
(Aggr
, Typ
, Occ
));
3102 Set_No_Initialization
(N
);
3103 Initialize_Discriminants
(N
, Typ
);
3104 end Convert_Aggr_In_Object_Decl
;
3106 -------------------------------------
3107 -- Convert_Array_Aggr_In_Allocator --
3108 -------------------------------------
3110 procedure Convert_Array_Aggr_In_Allocator
3115 Aggr_Code
: List_Id
;
3116 Typ
: constant Entity_Id
:= Etype
(Aggr
);
3117 Ctyp
: constant Entity_Id
:= Component_Type
(Typ
);
3120 -- The target is an explicit dereference of the allocated object.
3121 -- Generate component assignments to it, as for an aggregate that
3122 -- appears on the right-hand side of an assignment statement.
3125 Build_Array_Aggr_Code
(Aggr
,
3127 Index
=> First_Index
(Typ
),
3129 Scalar_Comp
=> Is_Scalar_Type
(Ctyp
));
3131 Insert_Actions_After
(Decl
, Aggr_Code
);
3132 end Convert_Array_Aggr_In_Allocator
;
3134 ----------------------------
3135 -- Convert_To_Assignments --
3136 ----------------------------
3138 procedure Convert_To_Assignments
(N
: Node_Id
; Typ
: Entity_Id
) is
3139 Loc
: constant Source_Ptr
:= Sloc
(N
);
3144 Target_Expr
: Node_Id
;
3145 Parent_Kind
: Node_Kind
;
3146 Unc_Decl
: Boolean := False;
3147 Parent_Node
: Node_Id
;
3150 pragma Assert
(not Is_Static_Dispatch_Table_Aggregate
(N
));
3151 pragma Assert
(Is_Record_Type
(Typ
));
3153 Parent_Node
:= Parent
(N
);
3154 Parent_Kind
:= Nkind
(Parent_Node
);
3156 if Parent_Kind
= N_Qualified_Expression
then
3158 -- Check if we are in a unconstrained declaration because in this
3159 -- case the current delayed expansion mechanism doesn't work when
3160 -- the declared object size depend on the initializing expr.
3163 Parent_Node
:= Parent
(Parent_Node
);
3164 Parent_Kind
:= Nkind
(Parent_Node
);
3166 if Parent_Kind
= N_Object_Declaration
then
3168 not Is_Entity_Name
(Object_Definition
(Parent_Node
))
3169 or else Has_Discriminants
3170 (Entity
(Object_Definition
(Parent_Node
)))
3171 or else Is_Class_Wide_Type
3172 (Entity
(Object_Definition
(Parent_Node
)));
3177 -- Just set the Delay flag in the cases where the transformation will be
3178 -- done top down from above.
3182 -- Internal aggregate (transformed when expanding the parent)
3184 or else Parent_Kind
= N_Aggregate
3185 or else Parent_Kind
= N_Extension_Aggregate
3186 or else Parent_Kind
= N_Component_Association
3188 -- Allocator (see Convert_Aggr_In_Allocator)
3190 or else Parent_Kind
= N_Allocator
3192 -- Object declaration (see Convert_Aggr_In_Object_Decl)
3194 or else (Parent_Kind
= N_Object_Declaration
and then not Unc_Decl
)
3196 -- Safe assignment (see Convert_Aggr_Assignments). So far only the
3197 -- assignments in init procs are taken into account.
3199 or else (Parent_Kind
= N_Assignment_Statement
3200 and then Inside_Init_Proc
)
3202 -- (Ada 2005) An inherently limited type in a return statement,
3203 -- which will be handled in a build-in-place fashion, and may be
3204 -- rewritten as an extended return and have its own finalization
3205 -- machinery. In the case of a simple return, the aggregate needs
3206 -- to be delayed until the scope for the return statement has been
3207 -- created, so that any finalization chain will be associated with
3208 -- that scope. For extended returns, we delay expansion to avoid the
3209 -- creation of an unwanted transient scope that could result in
3210 -- premature finalization of the return object (which is built in
3211 -- in place within the caller's scope).
3214 (Is_Immutably_Limited_Type
(Typ
)
3216 (Nkind
(Parent
(Parent_Node
)) = N_Extended_Return_Statement
3217 or else Nkind
(Parent_Node
) = N_Simple_Return_Statement
))
3219 Set_Expansion_Delayed
(N
);
3223 if Requires_Transient_Scope
(Typ
) then
3224 Establish_Transient_Scope
3226 Is_Controlled
(Typ
) or else Has_Controlled_Component
(Typ
));
3229 -- If the aggregate is non-limited, create a temporary. If it is limited
3230 -- and the context is an assignment, this is a subaggregate for an
3231 -- enclosing aggregate being expanded. It must be built in place, so use
3232 -- the target of the current assignment.
3234 if Is_Limited_Type
(Typ
)
3235 and then Nkind
(Parent
(N
)) = N_Assignment_Statement
3237 Target_Expr
:= New_Copy_Tree
(Name
(Parent
(N
)));
3238 Insert_Actions
(Parent
(N
),
3239 Build_Record_Aggr_Code
(N
, Typ
, Target_Expr
));
3240 Rewrite
(Parent
(N
), Make_Null_Statement
(Loc
));
3243 Temp
:= Make_Temporary
(Loc
, 'A', N
);
3245 -- If the type inherits unknown discriminants, use the view with
3246 -- known discriminants if available.
3248 if Has_Unknown_Discriminants
(Typ
)
3249 and then Present
(Underlying_Record_View
(Typ
))
3251 T
:= Underlying_Record_View
(Typ
);
3257 Make_Object_Declaration
(Loc
,
3258 Defining_Identifier
=> Temp
,
3259 Object_Definition
=> New_Occurrence_Of
(T
, Loc
));
3261 Set_No_Initialization
(Instr
);
3262 Insert_Action
(N
, Instr
);
3263 Initialize_Discriminants
(Instr
, T
);
3264 Target_Expr
:= New_Occurrence_Of
(Temp
, Loc
);
3265 Insert_Actions
(N
, Build_Record_Aggr_Code
(N
, T
, Target_Expr
));
3266 Rewrite
(N
, New_Occurrence_Of
(Temp
, Loc
));
3267 Analyze_And_Resolve
(N
, T
);
3269 end Convert_To_Assignments
;
3271 ---------------------------
3272 -- Convert_To_Positional --
3273 ---------------------------
3275 procedure Convert_To_Positional
3277 Max_Others_Replicate
: Nat
:= 5;
3278 Handle_Bit_Packed
: Boolean := False)
3280 Typ
: constant Entity_Id
:= Etype
(N
);
3282 Static_Components
: Boolean := True;
3284 procedure Check_Static_Components
;
3285 -- Check whether all components of the aggregate are compile-time known
3286 -- values, and can be passed as is to the back-end without further
3292 Ixb
: Node_Id
) return Boolean;
3293 -- Convert the aggregate into a purely positional form if possible. On
3294 -- entry the bounds of all dimensions are known to be static, and the
3295 -- total number of components is safe enough to expand.
3297 function Is_Flat
(N
: Node_Id
; Dims
: Int
) return Boolean;
3298 -- Return True iff the array N is flat (which is not trivial in the case
3299 -- of multidimensional aggregates).
3301 -----------------------------
3302 -- Check_Static_Components --
3303 -----------------------------
3305 procedure Check_Static_Components
is
3309 Static_Components
:= True;
3311 if Nkind
(N
) = N_String_Literal
then
3314 elsif Present
(Expressions
(N
)) then
3315 Expr
:= First
(Expressions
(N
));
3316 while Present
(Expr
) loop
3317 if Nkind
(Expr
) /= N_Aggregate
3318 or else not Compile_Time_Known_Aggregate
(Expr
)
3319 or else Expansion_Delayed
(Expr
)
3321 Static_Components
:= False;
3329 if Nkind
(N
) = N_Aggregate
3330 and then Present
(Component_Associations
(N
))
3332 Expr
:= First
(Component_Associations
(N
));
3333 while Present
(Expr
) loop
3334 if Nkind_In
(Expression
(Expr
), N_Integer_Literal
,
3339 elsif Is_Entity_Name
(Expression
(Expr
))
3340 and then Present
(Entity
(Expression
(Expr
)))
3341 and then Ekind
(Entity
(Expression
(Expr
))) =
3342 E_Enumeration_Literal
3346 elsif Nkind
(Expression
(Expr
)) /= N_Aggregate
3347 or else not Compile_Time_Known_Aggregate
(Expression
(Expr
))
3348 or else Expansion_Delayed
(Expression
(Expr
))
3350 Static_Components
:= False;
3357 end Check_Static_Components
;
3366 Ixb
: Node_Id
) return Boolean
3368 Loc
: constant Source_Ptr
:= Sloc
(N
);
3369 Blo
: constant Node_Id
:= Type_Low_Bound
(Etype
(Ixb
));
3370 Lo
: constant Node_Id
:= Type_Low_Bound
(Etype
(Ix
));
3371 Hi
: constant Node_Id
:= Type_High_Bound
(Etype
(Ix
));
3375 Others_Present
: Boolean := False;
3378 if Nkind
(Original_Node
(N
)) = N_String_Literal
then
3382 if not Compile_Time_Known_Value
(Lo
)
3383 or else not Compile_Time_Known_Value
(Hi
)
3388 Lov
:= Expr_Value
(Lo
);
3389 Hiv
:= Expr_Value
(Hi
);
3391 -- Check if there is an others choice
3393 if Present
(Component_Associations
(N
)) then
3399 Assoc
:= First
(Component_Associations
(N
));
3400 while Present
(Assoc
) loop
3402 -- If this is a box association, flattening is in general
3403 -- not possible because at this point we cannot tell if the
3404 -- default is static or even exists.
3406 if Box_Present
(Assoc
) then
3410 Choice
:= First
(Choices
(Assoc
));
3412 while Present
(Choice
) loop
3413 if Nkind
(Choice
) = N_Others_Choice
then
3414 Others_Present
:= True;
3425 -- If the low bound is not known at compile time and others is not
3426 -- present we can proceed since the bounds can be obtained from the
3429 -- Note: This case is required in VM platforms since their backends
3430 -- normalize array indexes in the range 0 .. N-1. Hence, if we do
3431 -- not flat an array whose bounds cannot be obtained from the type
3432 -- of the index the backend has no way to properly generate the code.
3433 -- See ACATS c460010 for an example.
3436 or else (not Compile_Time_Known_Value
(Blo
)
3437 and then Others_Present
)
3442 -- Determine if set of alternatives is suitable for conversion and
3443 -- build an array containing the values in sequence.
3446 Vals
: array (UI_To_Int
(Lov
) .. UI_To_Int
(Hiv
))
3447 of Node_Id
:= (others => Empty
);
3448 -- The values in the aggregate sorted appropriately
3451 -- Same data as Vals in list form
3454 -- Used to validate Max_Others_Replicate limit
3457 Num
: Int
:= UI_To_Int
(Lov
);
3463 if Present
(Expressions
(N
)) then
3464 Elmt
:= First
(Expressions
(N
));
3465 while Present
(Elmt
) loop
3466 if Nkind
(Elmt
) = N_Aggregate
3467 and then Present
(Next_Index
(Ix
))
3469 not Flatten
(Elmt
, Next_Index
(Ix
), Next_Index
(Ixb
))
3474 Vals
(Num
) := Relocate_Node
(Elmt
);
3481 if No
(Component_Associations
(N
)) then
3485 Elmt
:= First
(Component_Associations
(N
));
3487 if Nkind
(Expression
(Elmt
)) = N_Aggregate
then
3488 if Present
(Next_Index
(Ix
))
3491 (Expression
(Elmt
), Next_Index
(Ix
), Next_Index
(Ixb
))
3497 Component_Loop
: while Present
(Elmt
) loop
3498 Choice
:= First
(Choices
(Elmt
));
3499 Choice_Loop
: while Present
(Choice
) loop
3501 -- If we have an others choice, fill in the missing elements
3502 -- subject to the limit established by Max_Others_Replicate.
3504 if Nkind
(Choice
) = N_Others_Choice
then
3507 for J
in Vals
'Range loop
3508 if No
(Vals
(J
)) then
3509 Vals
(J
) := New_Copy_Tree
(Expression
(Elmt
));
3510 Rep_Count
:= Rep_Count
+ 1;
3512 -- Check for maximum others replication. Note that
3513 -- we skip this test if either of the restrictions
3514 -- No_Elaboration_Code or No_Implicit_Loops is
3515 -- active, if this is a preelaborable unit or a
3516 -- predefined unit. This ensures that predefined
3517 -- units get the same level of constant folding in
3518 -- Ada 95 and Ada 2005, where their categorization
3522 P
: constant Entity_Id
:=
3523 Cunit_Entity
(Current_Sem_Unit
);
3526 -- Check if duplication OK and if so continue
3529 if Restriction_Active
(No_Elaboration_Code
)
3530 or else Restriction_Active
(No_Implicit_Loops
)
3531 or else Is_Preelaborated
(P
)
3532 or else (Ekind
(P
) = E_Package_Body
3534 Is_Preelaborated
(Spec_Entity
(P
)))
3536 Is_Predefined_File_Name
3537 (Unit_File_Name
(Get_Source_Unit
(P
)))
3541 -- If duplication not OK, then we return False
3542 -- if the replication count is too high
3544 elsif Rep_Count
> Max_Others_Replicate
then
3547 -- Continue on if duplication not OK, but the
3548 -- replication count is not excessive.
3557 exit Component_Loop
;
3559 -- Case of a subtype mark, identifier or expanded name
3561 elsif Is_Entity_Name
(Choice
)
3562 and then Is_Type
(Entity
(Choice
))
3564 Lo
:= Type_Low_Bound
(Etype
(Choice
));
3565 Hi
:= Type_High_Bound
(Etype
(Choice
));
3567 -- Case of subtype indication
3569 elsif Nkind
(Choice
) = N_Subtype_Indication
then
3570 Lo
:= Low_Bound
(Range_Expression
(Constraint
(Choice
)));
3571 Hi
:= High_Bound
(Range_Expression
(Constraint
(Choice
)));
3575 elsif Nkind
(Choice
) = N_Range
then
3576 Lo
:= Low_Bound
(Choice
);
3577 Hi
:= High_Bound
(Choice
);
3579 -- Normal subexpression case
3581 else pragma Assert
(Nkind
(Choice
) in N_Subexpr
);
3582 if not Compile_Time_Known_Value
(Choice
) then
3586 Choice_Index
:= UI_To_Int
(Expr_Value
(Choice
));
3587 if Choice_Index
in Vals
'Range then
3588 Vals
(Choice_Index
) :=
3589 New_Copy_Tree
(Expression
(Elmt
));
3593 -- Choice is statically out-of-range, will be
3594 -- rewritten to raise Constraint_Error.
3601 -- Range cases merge with Lo,Hi set
3603 if not Compile_Time_Known_Value
(Lo
)
3605 not Compile_Time_Known_Value
(Hi
)
3609 for J
in UI_To_Int
(Expr_Value
(Lo
)) ..
3610 UI_To_Int
(Expr_Value
(Hi
))
3612 Vals
(J
) := New_Copy_Tree
(Expression
(Elmt
));
3618 end loop Choice_Loop
;
3621 end loop Component_Loop
;
3623 -- If we get here the conversion is possible
3626 for J
in Vals
'Range loop
3627 Append
(Vals
(J
), Vlist
);
3630 Rewrite
(N
, Make_Aggregate
(Loc
, Expressions
=> Vlist
));
3631 Set_Aggregate_Bounds
(N
, Aggregate_Bounds
(Original_Node
(N
)));
3640 function Is_Flat
(N
: Node_Id
; Dims
: Int
) return Boolean is
3647 elsif Nkind
(N
) = N_Aggregate
then
3648 if Present
(Component_Associations
(N
)) then
3652 Elmt
:= First
(Expressions
(N
));
3653 while Present
(Elmt
) loop
3654 if not Is_Flat
(Elmt
, Dims
- 1) then
3668 -- Start of processing for Convert_To_Positional
3671 -- Ada 2005 (AI-287): Do not convert in case of default initialized
3672 -- components because in this case will need to call the corresponding
3675 if Has_Default_Init_Comps
(N
) then
3679 if Is_Flat
(N
, Number_Dimensions
(Typ
)) then
3683 if Is_Bit_Packed_Array
(Typ
)
3684 and then not Handle_Bit_Packed
3689 -- Do not convert to positional if controlled components are involved
3690 -- since these require special processing
3692 if Has_Controlled_Component
(Typ
) then
3696 Check_Static_Components
;
3698 -- If the size is known, or all the components are static, try to
3699 -- build a fully positional aggregate.
3701 -- The size of the type may not be known for an aggregate with
3702 -- discriminated array components, but if the components are static
3703 -- it is still possible to verify statically that the length is
3704 -- compatible with the upper bound of the type, and therefore it is
3705 -- worth flattening such aggregates as well.
3707 -- For now the back-end expands these aggregates into individual
3708 -- assignments to the target anyway, but it is conceivable that
3709 -- it will eventually be able to treat such aggregates statically???
3711 if Aggr_Size_OK
(N
, Typ
)
3712 and then Flatten
(N
, First_Index
(Typ
), First_Index
(Base_Type
(Typ
)))
3714 if Static_Components
then
3715 Set_Compile_Time_Known_Aggregate
(N
);
3716 Set_Expansion_Delayed
(N
, False);
3719 Analyze_And_Resolve
(N
, Typ
);
3721 end Convert_To_Positional
;
3723 ----------------------------
3724 -- Expand_Array_Aggregate --
3725 ----------------------------
3727 -- Array aggregate expansion proceeds as follows:
3729 -- 1. If requested we generate code to perform all the array aggregate
3730 -- bound checks, specifically
3732 -- (a) Check that the index range defined by aggregate bounds is
3733 -- compatible with corresponding index subtype.
3735 -- (b) If an others choice is present check that no aggregate
3736 -- index is outside the bounds of the index constraint.
3738 -- (c) For multidimensional arrays make sure that all subaggregates
3739 -- corresponding to the same dimension have the same bounds.
3741 -- 2. Check for packed array aggregate which can be converted to a
3742 -- constant so that the aggregate disappeares completely.
3744 -- 3. Check case of nested aggregate. Generally nested aggregates are
3745 -- handled during the processing of the parent aggregate.
3747 -- 4. Check if the aggregate can be statically processed. If this is the
3748 -- case pass it as is to Gigi. Note that a necessary condition for
3749 -- static processing is that the aggregate be fully positional.
3751 -- 5. If in place aggregate expansion is possible (i.e. no need to create
3752 -- a temporary) then mark the aggregate as such and return. Otherwise
3753 -- create a new temporary and generate the appropriate initialization
3756 procedure Expand_Array_Aggregate
(N
: Node_Id
) is
3757 Loc
: constant Source_Ptr
:= Sloc
(N
);
3759 Typ
: constant Entity_Id
:= Etype
(N
);
3760 Ctyp
: constant Entity_Id
:= Component_Type
(Typ
);
3761 -- Typ is the correct constrained array subtype of the aggregate
3762 -- Ctyp is the corresponding component type.
3764 Aggr_Dimension
: constant Pos
:= Number_Dimensions
(Typ
);
3765 -- Number of aggregate index dimensions
3767 Aggr_Low
: array (1 .. Aggr_Dimension
) of Node_Id
;
3768 Aggr_High
: array (1 .. Aggr_Dimension
) of Node_Id
;
3769 -- Low and High bounds of the constraint for each aggregate index
3771 Aggr_Index_Typ
: array (1 .. Aggr_Dimension
) of Entity_Id
;
3772 -- The type of each index
3774 Maybe_In_Place_OK
: Boolean;
3775 -- If the type is neither controlled nor packed and the aggregate
3776 -- is the expression in an assignment, assignment in place may be
3777 -- possible, provided other conditions are met on the LHS.
3779 Others_Present
: array (1 .. Aggr_Dimension
) of Boolean :=
3781 -- If Others_Present (J) is True, then there is an others choice
3782 -- in one of the sub-aggregates of N at dimension J.
3784 procedure Build_Constrained_Type
(Positional
: Boolean);
3785 -- If the subtype is not static or unconstrained, build a constrained
3786 -- type using the computable sizes of the aggregate and its sub-
3789 procedure Check_Bounds
(Aggr_Bounds
: Node_Id
; Index_Bounds
: Node_Id
);
3790 -- Checks that the bounds of Aggr_Bounds are within the bounds defined
3793 procedure Check_Same_Aggr_Bounds
(Sub_Aggr
: Node_Id
; Dim
: Pos
);
3794 -- Checks that in a multi-dimensional array aggregate all subaggregates
3795 -- corresponding to the same dimension have the same bounds.
3796 -- Sub_Aggr is an array sub-aggregate. Dim is the dimension
3797 -- corresponding to the sub-aggregate.
3799 procedure Compute_Others_Present
(Sub_Aggr
: Node_Id
; Dim
: Pos
);
3800 -- Computes the values of array Others_Present. Sub_Aggr is the
3801 -- array sub-aggregate we start the computation from. Dim is the
3802 -- dimension corresponding to the sub-aggregate.
3804 function In_Place_Assign_OK
return Boolean;
3805 -- Simple predicate to determine whether an aggregate assignment can
3806 -- be done in place, because none of the new values can depend on the
3807 -- components of the target of the assignment.
3809 procedure Others_Check
(Sub_Aggr
: Node_Id
; Dim
: Pos
);
3810 -- Checks that if an others choice is present in any sub-aggregate no
3811 -- aggregate index is outside the bounds of the index constraint.
3812 -- Sub_Aggr is an array sub-aggregate. Dim is the dimension
3813 -- corresponding to the sub-aggregate.
3815 function Safe_Left_Hand_Side
(N
: Node_Id
) return Boolean;
3816 -- In addition to Maybe_In_Place_OK, in order for an aggregate to be
3817 -- built directly into the target of the assignment it must be free
3820 ----------------------------
3821 -- Build_Constrained_Type --
3822 ----------------------------
3824 procedure Build_Constrained_Type
(Positional
: Boolean) is
3825 Loc
: constant Source_Ptr
:= Sloc
(N
);
3826 Agg_Type
: constant Entity_Id
:= Make_Temporary
(Loc
, 'A');
3829 Typ
: constant Entity_Id
:= Etype
(N
);
3830 Indexes
: constant List_Id
:= New_List
;
3835 -- If the aggregate is purely positional, all its subaggregates
3836 -- have the same size. We collect the dimensions from the first
3837 -- subaggregate at each level.
3842 for D
in 1 .. Number_Dimensions
(Typ
) loop
3843 Sub_Agg
:= First
(Expressions
(Sub_Agg
));
3847 while Present
(Comp
) loop
3854 Low_Bound
=> Make_Integer_Literal
(Loc
, 1),
3855 High_Bound
=> Make_Integer_Literal
(Loc
, Num
)));
3859 -- We know the aggregate type is unconstrained and the aggregate
3860 -- is not processable by the back end, therefore not necessarily
3861 -- positional. Retrieve each dimension bounds (computed earlier).
3863 for D
in 1 .. Number_Dimensions
(Typ
) loop
3866 Low_Bound
=> Aggr_Low
(D
),
3867 High_Bound
=> Aggr_High
(D
)),
3873 Make_Full_Type_Declaration
(Loc
,
3874 Defining_Identifier
=> Agg_Type
,
3876 Make_Constrained_Array_Definition
(Loc
,
3877 Discrete_Subtype_Definitions
=> Indexes
,
3878 Component_Definition
=>
3879 Make_Component_Definition
(Loc
,
3880 Aliased_Present
=> False,
3881 Subtype_Indication
=>
3882 New_Occurrence_Of
(Component_Type
(Typ
), Loc
))));
3884 Insert_Action
(N
, Decl
);
3886 Set_Etype
(N
, Agg_Type
);
3887 Set_Is_Itype
(Agg_Type
);
3888 Freeze_Itype
(Agg_Type
, N
);
3889 end Build_Constrained_Type
;
3895 procedure Check_Bounds
(Aggr_Bounds
: Node_Id
; Index_Bounds
: Node_Id
) is
3902 Cond
: Node_Id
:= Empty
;
3905 Get_Index_Bounds
(Aggr_Bounds
, Aggr_Lo
, Aggr_Hi
);
3906 Get_Index_Bounds
(Index_Bounds
, Ind_Lo
, Ind_Hi
);
3908 -- Generate the following test:
3910 -- [constraint_error when
3911 -- Aggr_Lo <= Aggr_Hi and then
3912 -- (Aggr_Lo < Ind_Lo or else Aggr_Hi > Ind_Hi)]
3914 -- As an optimization try to see if some tests are trivially vacuous
3915 -- because we are comparing an expression against itself.
3917 if Aggr_Lo
= Ind_Lo
and then Aggr_Hi
= Ind_Hi
then
3920 elsif Aggr_Hi
= Ind_Hi
then
3923 Left_Opnd
=> Duplicate_Subexpr_Move_Checks
(Aggr_Lo
),
3924 Right_Opnd
=> Duplicate_Subexpr_Move_Checks
(Ind_Lo
));
3926 elsif Aggr_Lo
= Ind_Lo
then
3929 Left_Opnd
=> Duplicate_Subexpr_Move_Checks
(Aggr_Hi
),
3930 Right_Opnd
=> Duplicate_Subexpr_Move_Checks
(Ind_Hi
));
3937 Left_Opnd
=> Duplicate_Subexpr_Move_Checks
(Aggr_Lo
),
3938 Right_Opnd
=> Duplicate_Subexpr_Move_Checks
(Ind_Lo
)),
3942 Left_Opnd
=> Duplicate_Subexpr
(Aggr_Hi
),
3943 Right_Opnd
=> Duplicate_Subexpr
(Ind_Hi
)));
3946 if Present
(Cond
) then
3951 Left_Opnd
=> Duplicate_Subexpr_Move_Checks
(Aggr_Lo
),
3952 Right_Opnd
=> Duplicate_Subexpr_Move_Checks
(Aggr_Hi
)),
3954 Right_Opnd
=> Cond
);
3956 Set_Analyzed
(Left_Opnd
(Left_Opnd
(Cond
)), False);
3957 Set_Analyzed
(Right_Opnd
(Left_Opnd
(Cond
)), False);
3959 Make_Raise_Constraint_Error
(Loc
,
3961 Reason
=> CE_Length_Check_Failed
));
3965 ----------------------------
3966 -- Check_Same_Aggr_Bounds --
3967 ----------------------------
3969 procedure Check_Same_Aggr_Bounds
(Sub_Aggr
: Node_Id
; Dim
: Pos
) is
3970 Sub_Lo
: constant Node_Id
:= Low_Bound
(Aggregate_Bounds
(Sub_Aggr
));
3971 Sub_Hi
: constant Node_Id
:= High_Bound
(Aggregate_Bounds
(Sub_Aggr
));
3972 -- The bounds of this specific sub-aggregate
3974 Aggr_Lo
: constant Node_Id
:= Aggr_Low
(Dim
);
3975 Aggr_Hi
: constant Node_Id
:= Aggr_High
(Dim
);
3976 -- The bounds of the aggregate for this dimension
3978 Ind_Typ
: constant Entity_Id
:= Aggr_Index_Typ
(Dim
);
3979 -- The index type for this dimension.xxx
3981 Cond
: Node_Id
:= Empty
;
3986 -- If index checks are on generate the test
3988 -- [constraint_error when
3989 -- Aggr_Lo /= Sub_Lo or else Aggr_Hi /= Sub_Hi]
3991 -- As an optimization try to see if some tests are trivially vacuos
3992 -- because we are comparing an expression against itself. Also for
3993 -- the first dimension the test is trivially vacuous because there
3994 -- is just one aggregate for dimension 1.
3996 if Index_Checks_Suppressed
(Ind_Typ
) then
4000 or else (Aggr_Lo
= Sub_Lo
and then Aggr_Hi
= Sub_Hi
)
4004 elsif Aggr_Hi
= Sub_Hi
then
4007 Left_Opnd
=> Duplicate_Subexpr_Move_Checks
(Aggr_Lo
),
4008 Right_Opnd
=> Duplicate_Subexpr_Move_Checks
(Sub_Lo
));
4010 elsif Aggr_Lo
= Sub_Lo
then
4013 Left_Opnd
=> Duplicate_Subexpr_Move_Checks
(Aggr_Hi
),
4014 Right_Opnd
=> Duplicate_Subexpr_Move_Checks
(Sub_Hi
));
4021 Left_Opnd
=> Duplicate_Subexpr_Move_Checks
(Aggr_Lo
),
4022 Right_Opnd
=> Duplicate_Subexpr_Move_Checks
(Sub_Lo
)),
4026 Left_Opnd
=> Duplicate_Subexpr
(Aggr_Hi
),
4027 Right_Opnd
=> Duplicate_Subexpr
(Sub_Hi
)));
4030 if Present
(Cond
) then
4032 Make_Raise_Constraint_Error
(Loc
,
4034 Reason
=> CE_Length_Check_Failed
));
4037 -- Now look inside the sub-aggregate to see if there is more work
4039 if Dim
< Aggr_Dimension
then
4041 -- Process positional components
4043 if Present
(Expressions
(Sub_Aggr
)) then
4044 Expr
:= First
(Expressions
(Sub_Aggr
));
4045 while Present
(Expr
) loop
4046 Check_Same_Aggr_Bounds
(Expr
, Dim
+ 1);
4051 -- Process component associations
4053 if Present
(Component_Associations
(Sub_Aggr
)) then
4054 Assoc
:= First
(Component_Associations
(Sub_Aggr
));
4055 while Present
(Assoc
) loop
4056 Expr
:= Expression
(Assoc
);
4057 Check_Same_Aggr_Bounds
(Expr
, Dim
+ 1);
4062 end Check_Same_Aggr_Bounds
;
4064 ----------------------------
4065 -- Compute_Others_Present --
4066 ----------------------------
4068 procedure Compute_Others_Present
(Sub_Aggr
: Node_Id
; Dim
: Pos
) is
4073 if Present
(Component_Associations
(Sub_Aggr
)) then
4074 Assoc
:= Last
(Component_Associations
(Sub_Aggr
));
4076 if Nkind
(First
(Choices
(Assoc
))) = N_Others_Choice
then
4077 Others_Present
(Dim
) := True;
4081 -- Now look inside the sub-aggregate to see if there is more work
4083 if Dim
< Aggr_Dimension
then
4085 -- Process positional components
4087 if Present
(Expressions
(Sub_Aggr
)) then
4088 Expr
:= First
(Expressions
(Sub_Aggr
));
4089 while Present
(Expr
) loop
4090 Compute_Others_Present
(Expr
, Dim
+ 1);
4095 -- Process component associations
4097 if Present
(Component_Associations
(Sub_Aggr
)) then
4098 Assoc
:= First
(Component_Associations
(Sub_Aggr
));
4099 while Present
(Assoc
) loop
4100 Expr
:= Expression
(Assoc
);
4101 Compute_Others_Present
(Expr
, Dim
+ 1);
4106 end Compute_Others_Present
;
4108 ------------------------
4109 -- In_Place_Assign_OK --
4110 ------------------------
4112 function In_Place_Assign_OK
return Boolean is
4120 function Safe_Aggregate
(Aggr
: Node_Id
) return Boolean;
4121 -- Check recursively that each component of a (sub)aggregate does
4122 -- not depend on the variable being assigned to.
4124 function Safe_Component
(Expr
: Node_Id
) return Boolean;
4125 -- Verify that an expression cannot depend on the variable being
4126 -- assigned to. Room for improvement here (but less than before).
4128 --------------------
4129 -- Safe_Aggregate --
4130 --------------------
4132 function Safe_Aggregate
(Aggr
: Node_Id
) return Boolean is
4136 if Present
(Expressions
(Aggr
)) then
4137 Expr
:= First
(Expressions
(Aggr
));
4138 while Present
(Expr
) loop
4139 if Nkind
(Expr
) = N_Aggregate
then
4140 if not Safe_Aggregate
(Expr
) then
4144 elsif not Safe_Component
(Expr
) then
4152 if Present
(Component_Associations
(Aggr
)) then
4153 Expr
:= First
(Component_Associations
(Aggr
));
4154 while Present
(Expr
) loop
4155 if Nkind
(Expression
(Expr
)) = N_Aggregate
then
4156 if not Safe_Aggregate
(Expression
(Expr
)) then
4160 -- If association has a box, no way to determine yet
4161 -- whether default can be assigned in place.
4163 elsif Box_Present
(Expr
) then
4166 elsif not Safe_Component
(Expression
(Expr
)) then
4177 --------------------
4178 -- Safe_Component --
4179 --------------------
4181 function Safe_Component
(Expr
: Node_Id
) return Boolean is
4182 Comp
: Node_Id
:= Expr
;
4184 function Check_Component
(Comp
: Node_Id
) return Boolean;
4185 -- Do the recursive traversal, after copy
4187 ---------------------
4188 -- Check_Component --
4189 ---------------------
4191 function Check_Component
(Comp
: Node_Id
) return Boolean is
4193 if Is_Overloaded
(Comp
) then
4197 return Compile_Time_Known_Value
(Comp
)
4199 or else (Is_Entity_Name
(Comp
)
4200 and then Present
(Entity
(Comp
))
4201 and then No
(Renamed_Object
(Entity
(Comp
))))
4203 or else (Nkind
(Comp
) = N_Attribute_Reference
4204 and then Check_Component
(Prefix
(Comp
)))
4206 or else (Nkind
(Comp
) in N_Binary_Op
4207 and then Check_Component
(Left_Opnd
(Comp
))
4208 and then Check_Component
(Right_Opnd
(Comp
)))
4210 or else (Nkind
(Comp
) in N_Unary_Op
4211 and then Check_Component
(Right_Opnd
(Comp
)))
4213 or else (Nkind
(Comp
) = N_Selected_Component
4214 and then Check_Component
(Prefix
(Comp
)))
4216 or else (Nkind
(Comp
) = N_Unchecked_Type_Conversion
4217 and then Check_Component
(Expression
(Comp
)));
4218 end Check_Component
;
4220 -- Start of processing for Safe_Component
4223 -- If the component appears in an association that may
4224 -- correspond to more than one element, it is not analyzed
4225 -- before the expansion into assignments, to avoid side effects.
4226 -- We analyze, but do not resolve the copy, to obtain sufficient
4227 -- entity information for the checks that follow. If component is
4228 -- overloaded we assume an unsafe function call.
4230 if not Analyzed
(Comp
) then
4231 if Is_Overloaded
(Expr
) then
4234 elsif Nkind
(Expr
) = N_Aggregate
4235 and then not Is_Others_Aggregate
(Expr
)
4239 elsif Nkind
(Expr
) = N_Allocator
then
4241 -- For now, too complex to analyze
4246 Comp
:= New_Copy_Tree
(Expr
);
4247 Set_Parent
(Comp
, Parent
(Expr
));
4251 if Nkind
(Comp
) = N_Aggregate
then
4252 return Safe_Aggregate
(Comp
);
4254 return Check_Component
(Comp
);
4258 -- Start of processing for In_Place_Assign_OK
4261 if Present
(Component_Associations
(N
)) then
4263 -- On assignment, sliding can take place, so we cannot do the
4264 -- assignment in place unless the bounds of the aggregate are
4265 -- statically equal to those of the target.
4267 -- If the aggregate is given by an others choice, the bounds
4268 -- are derived from the left-hand side, and the assignment is
4269 -- safe if the expression is.
4271 if Is_Others_Aggregate
(N
) then
4274 (Expression
(First
(Component_Associations
(N
))));
4277 Aggr_In
:= First_Index
(Etype
(N
));
4279 if Nkind
(Parent
(N
)) = N_Assignment_Statement
then
4280 Obj_In
:= First_Index
(Etype
(Name
(Parent
(N
))));
4283 -- Context is an allocator. Check bounds of aggregate
4284 -- against given type in qualified expression.
4286 pragma Assert
(Nkind
(Parent
(Parent
(N
))) = N_Allocator
);
4288 First_Index
(Etype
(Entity
(Subtype_Mark
(Parent
(N
)))));
4291 while Present
(Aggr_In
) loop
4292 Get_Index_Bounds
(Aggr_In
, Aggr_Lo
, Aggr_Hi
);
4293 Get_Index_Bounds
(Obj_In
, Obj_Lo
, Obj_Hi
);
4295 if not Compile_Time_Known_Value
(Aggr_Lo
)
4296 or else not Compile_Time_Known_Value
(Aggr_Hi
)
4297 or else not Compile_Time_Known_Value
(Obj_Lo
)
4298 or else not Compile_Time_Known_Value
(Obj_Hi
)
4299 or else Expr_Value
(Aggr_Lo
) /= Expr_Value
(Obj_Lo
)
4300 or else Expr_Value
(Aggr_Hi
) /= Expr_Value
(Obj_Hi
)
4305 Next_Index
(Aggr_In
);
4306 Next_Index
(Obj_In
);
4310 -- Now check the component values themselves
4312 return Safe_Aggregate
(N
);
4313 end In_Place_Assign_OK
;
4319 procedure Others_Check
(Sub_Aggr
: Node_Id
; Dim
: Pos
) is
4320 Aggr_Lo
: constant Node_Id
:= Aggr_Low
(Dim
);
4321 Aggr_Hi
: constant Node_Id
:= Aggr_High
(Dim
);
4322 -- The bounds of the aggregate for this dimension
4324 Ind_Typ
: constant Entity_Id
:= Aggr_Index_Typ
(Dim
);
4325 -- The index type for this dimension
4327 Need_To_Check
: Boolean := False;
4329 Choices_Lo
: Node_Id
:= Empty
;
4330 Choices_Hi
: Node_Id
:= Empty
;
4331 -- The lowest and highest discrete choices for a named sub-aggregate
4333 Nb_Choices
: Int
:= -1;
4334 -- The number of discrete non-others choices in this sub-aggregate
4336 Nb_Elements
: Uint
:= Uint_0
;
4337 -- The number of elements in a positional aggregate
4339 Cond
: Node_Id
:= Empty
;
4346 -- Check if we have an others choice. If we do make sure that this
4347 -- sub-aggregate contains at least one element in addition to the
4350 if Range_Checks_Suppressed
(Ind_Typ
) then
4351 Need_To_Check
:= False;
4353 elsif Present
(Expressions
(Sub_Aggr
))
4354 and then Present
(Component_Associations
(Sub_Aggr
))
4356 Need_To_Check
:= True;
4358 elsif Present
(Component_Associations
(Sub_Aggr
)) then
4359 Assoc
:= Last
(Component_Associations
(Sub_Aggr
));
4361 if Nkind
(First
(Choices
(Assoc
))) /= N_Others_Choice
then
4362 Need_To_Check
:= False;
4365 -- Count the number of discrete choices. Start with -1 because
4366 -- the others choice does not count.
4369 Assoc
:= First
(Component_Associations
(Sub_Aggr
));
4370 while Present
(Assoc
) loop
4371 Choice
:= First
(Choices
(Assoc
));
4372 while Present
(Choice
) loop
4373 Nb_Choices
:= Nb_Choices
+ 1;
4380 -- If there is only an others choice nothing to do
4382 Need_To_Check
:= (Nb_Choices
> 0);
4386 Need_To_Check
:= False;
4389 -- If we are dealing with a positional sub-aggregate with an others
4390 -- choice then compute the number or positional elements.
4392 if Need_To_Check
and then Present
(Expressions
(Sub_Aggr
)) then
4393 Expr
:= First
(Expressions
(Sub_Aggr
));
4394 Nb_Elements
:= Uint_0
;
4395 while Present
(Expr
) loop
4396 Nb_Elements
:= Nb_Elements
+ 1;
4400 -- If the aggregate contains discrete choices and an others choice
4401 -- compute the smallest and largest discrete choice values.
4403 elsif Need_To_Check
then
4404 Compute_Choices_Lo_And_Choices_Hi
: declare
4406 Table
: Case_Table_Type
(1 .. Nb_Choices
);
4407 -- Used to sort all the different choice values
4414 Assoc
:= First
(Component_Associations
(Sub_Aggr
));
4415 while Present
(Assoc
) loop
4416 Choice
:= First
(Choices
(Assoc
));
4417 while Present
(Choice
) loop
4418 if Nkind
(Choice
) = N_Others_Choice
then
4422 Get_Index_Bounds
(Choice
, Low
, High
);
4423 Table
(J
).Choice_Lo
:= Low
;
4424 Table
(J
).Choice_Hi
:= High
;
4433 -- Sort the discrete choices
4435 Sort_Case_Table
(Table
);
4437 Choices_Lo
:= Table
(1).Choice_Lo
;
4438 Choices_Hi
:= Table
(Nb_Choices
).Choice_Hi
;
4439 end Compute_Choices_Lo_And_Choices_Hi
;
4442 -- If no others choice in this sub-aggregate, or the aggregate
4443 -- comprises only an others choice, nothing to do.
4445 if not Need_To_Check
then
4448 -- If we are dealing with an aggregate containing an others choice
4449 -- and positional components, we generate the following test:
4451 -- if Ind_Typ'Pos (Aggr_Lo) + (Nb_Elements - 1) >
4452 -- Ind_Typ'Pos (Aggr_Hi)
4454 -- raise Constraint_Error;
4457 elsif Nb_Elements
> Uint_0
then
4463 Make_Attribute_Reference
(Loc
,
4464 Prefix
=> New_Reference_To
(Ind_Typ
, Loc
),
4465 Attribute_Name
=> Name_Pos
,
4468 (Duplicate_Subexpr_Move_Checks
(Aggr_Lo
))),
4469 Right_Opnd
=> Make_Integer_Literal
(Loc
, Nb_Elements
- 1)),
4472 Make_Attribute_Reference
(Loc
,
4473 Prefix
=> New_Reference_To
(Ind_Typ
, Loc
),
4474 Attribute_Name
=> Name_Pos
,
4475 Expressions
=> New_List
(
4476 Duplicate_Subexpr_Move_Checks
(Aggr_Hi
))));
4478 -- If we are dealing with an aggregate containing an others choice
4479 -- and discrete choices we generate the following test:
4481 -- [constraint_error when
4482 -- Choices_Lo < Aggr_Lo or else Choices_Hi > Aggr_Hi];
4490 Duplicate_Subexpr_Move_Checks
(Choices_Lo
),
4492 Duplicate_Subexpr_Move_Checks
(Aggr_Lo
)),
4497 Duplicate_Subexpr
(Choices_Hi
),
4499 Duplicate_Subexpr
(Aggr_Hi
)));
4502 if Present
(Cond
) then
4504 Make_Raise_Constraint_Error
(Loc
,
4506 Reason
=> CE_Length_Check_Failed
));
4507 -- Questionable reason code, shouldn't that be a
4508 -- CE_Range_Check_Failed ???
4511 -- Now look inside the sub-aggregate to see if there is more work
4513 if Dim
< Aggr_Dimension
then
4515 -- Process positional components
4517 if Present
(Expressions
(Sub_Aggr
)) then
4518 Expr
:= First
(Expressions
(Sub_Aggr
));
4519 while Present
(Expr
) loop
4520 Others_Check
(Expr
, Dim
+ 1);
4525 -- Process component associations
4527 if Present
(Component_Associations
(Sub_Aggr
)) then
4528 Assoc
:= First
(Component_Associations
(Sub_Aggr
));
4529 while Present
(Assoc
) loop
4530 Expr
:= Expression
(Assoc
);
4531 Others_Check
(Expr
, Dim
+ 1);
4538 -------------------------
4539 -- Safe_Left_Hand_Side --
4540 -------------------------
4542 function Safe_Left_Hand_Side
(N
: Node_Id
) return Boolean is
4543 function Is_Safe_Index
(Indx
: Node_Id
) return Boolean;
4544 -- If the left-hand side includes an indexed component, check that
4545 -- the indexes are free of side-effect.
4551 function Is_Safe_Index
(Indx
: Node_Id
) return Boolean is
4553 if Is_Entity_Name
(Indx
) then
4556 elsif Nkind
(Indx
) = N_Integer_Literal
then
4559 elsif Nkind
(Indx
) = N_Function_Call
4560 and then Is_Entity_Name
(Name
(Indx
))
4562 Has_Pragma_Pure_Function
(Entity
(Name
(Indx
)))
4566 elsif Nkind
(Indx
) = N_Type_Conversion
4567 and then Is_Safe_Index
(Expression
(Indx
))
4576 -- Start of processing for Safe_Left_Hand_Side
4579 if Is_Entity_Name
(N
) then
4582 elsif Nkind_In
(N
, N_Explicit_Dereference
, N_Selected_Component
)
4583 and then Safe_Left_Hand_Side
(Prefix
(N
))
4587 elsif Nkind
(N
) = N_Indexed_Component
4588 and then Safe_Left_Hand_Side
(Prefix
(N
))
4590 Is_Safe_Index
(First
(Expressions
(N
)))
4594 elsif Nkind
(N
) = N_Unchecked_Type_Conversion
then
4595 return Safe_Left_Hand_Side
(Expression
(N
));
4600 end Safe_Left_Hand_Side
;
4605 -- Holds the temporary aggregate value
4608 -- Holds the declaration of Tmp
4610 Aggr_Code
: List_Id
;
4611 Parent_Node
: Node_Id
;
4612 Parent_Kind
: Node_Kind
;
4614 -- Start of processing for Expand_Array_Aggregate
4617 -- Do not touch the special aggregates of attributes used for Asm calls
4619 if Is_RTE
(Ctyp
, RE_Asm_Input_Operand
)
4620 or else Is_RTE
(Ctyp
, RE_Asm_Output_Operand
)
4624 -- Do not expand an aggregate for an array type which contains tasks if
4625 -- the aggregate is associated with an unexpanded return statement of a
4626 -- build-in-place function. The aggregate is expanded when the related
4627 -- return statement (rewritten into an extended return) is processed.
4628 -- This delay ensures that any temporaries and initialization code
4629 -- generated for the aggregate appear in the proper return block and
4630 -- use the correct _chain and _master.
4632 elsif Has_Task
(Base_Type
(Etype
(N
)))
4633 and then Nkind
(Parent
(N
)) = N_Simple_Return_Statement
4634 and then Is_Build_In_Place_Function
4635 (Return_Applies_To
(Return_Statement_Entity
(Parent
(N
))))
4640 -- If the semantic analyzer has determined that aggregate N will raise
4641 -- Constraint_Error at run time, then the aggregate node has been
4642 -- replaced with an N_Raise_Constraint_Error node and we should
4645 pragma Assert
(not Raises_Constraint_Error
(N
));
4649 -- Check that the index range defined by aggregate bounds is
4650 -- compatible with corresponding index subtype.
4652 Index_Compatibility_Check
: declare
4653 Aggr_Index_Range
: Node_Id
:= First_Index
(Typ
);
4654 -- The current aggregate index range
4656 Index_Constraint
: Node_Id
:= First_Index
(Etype
(Typ
));
4657 -- The corresponding index constraint against which we have to
4658 -- check the above aggregate index range.
4661 Compute_Others_Present
(N
, 1);
4663 for J
in 1 .. Aggr_Dimension
loop
4664 -- There is no need to emit a check if an others choice is
4665 -- present for this array aggregate dimension since in this
4666 -- case one of N's sub-aggregates has taken its bounds from the
4667 -- context and these bounds must have been checked already. In
4668 -- addition all sub-aggregates corresponding to the same
4669 -- dimension must all have the same bounds (checked in (c) below).
4671 if not Range_Checks_Suppressed
(Etype
(Index_Constraint
))
4672 and then not Others_Present
(J
)
4674 -- We don't use Checks.Apply_Range_Check here because it emits
4675 -- a spurious check. Namely it checks that the range defined by
4676 -- the aggregate bounds is non empty. But we know this already
4679 Check_Bounds
(Aggr_Index_Range
, Index_Constraint
);
4682 -- Save the low and high bounds of the aggregate index as well as
4683 -- the index type for later use in checks (b) and (c) below.
4685 Aggr_Low
(J
) := Low_Bound
(Aggr_Index_Range
);
4686 Aggr_High
(J
) := High_Bound
(Aggr_Index_Range
);
4688 Aggr_Index_Typ
(J
) := Etype
(Index_Constraint
);
4690 Next_Index
(Aggr_Index_Range
);
4691 Next_Index
(Index_Constraint
);
4693 end Index_Compatibility_Check
;
4697 -- If an others choice is present check that no aggregate index is
4698 -- outside the bounds of the index constraint.
4700 Others_Check
(N
, 1);
4704 -- For multidimensional arrays make sure that all subaggregates
4705 -- corresponding to the same dimension have the same bounds.
4707 if Aggr_Dimension
> 1 then
4708 Check_Same_Aggr_Bounds
(N
, 1);
4713 -- Here we test for is packed array aggregate that we can handle at
4714 -- compile time. If so, return with transformation done. Note that we do
4715 -- this even if the aggregate is nested, because once we have done this
4716 -- processing, there is no more nested aggregate!
4718 if Packed_Array_Aggregate_Handled
(N
) then
4722 -- At this point we try to convert to positional form
4724 if Ekind
(Current_Scope
) = E_Package
4725 and then Static_Elaboration_Desired
(Current_Scope
)
4727 Convert_To_Positional
(N
, Max_Others_Replicate
=> 100);
4729 Convert_To_Positional
(N
);
4732 -- if the result is no longer an aggregate (e.g. it may be a string
4733 -- literal, or a temporary which has the needed value), then we are
4734 -- done, since there is no longer a nested aggregate.
4736 if Nkind
(N
) /= N_Aggregate
then
4739 -- We are also done if the result is an analyzed aggregate
4740 -- This case could use more comments ???
4743 and then N
/= Original_Node
(N
)
4748 -- If all aggregate components are compile-time known and the aggregate
4749 -- has been flattened, nothing left to do. The same occurs if the
4750 -- aggregate is used to initialize the components of an statically
4751 -- allocated dispatch table.
4753 if Compile_Time_Known_Aggregate
(N
)
4754 or else Is_Static_Dispatch_Table_Aggregate
(N
)
4756 Set_Expansion_Delayed
(N
, False);
4760 -- Now see if back end processing is possible
4762 if Backend_Processing_Possible
(N
) then
4764 -- If the aggregate is static but the constraints are not, build
4765 -- a static subtype for the aggregate, so that Gigi can place it
4766 -- in static memory. Perform an unchecked_conversion to the non-
4767 -- static type imposed by the context.
4770 Itype
: constant Entity_Id
:= Etype
(N
);
4772 Needs_Type
: Boolean := False;
4775 Index
:= First_Index
(Itype
);
4776 while Present
(Index
) loop
4777 if not Is_Static_Subtype
(Etype
(Index
)) then
4786 Build_Constrained_Type
(Positional
=> True);
4787 Rewrite
(N
, Unchecked_Convert_To
(Itype
, N
));
4797 -- Delay expansion for nested aggregates: it will be taken care of
4798 -- when the parent aggregate is expanded.
4800 Parent_Node
:= Parent
(N
);
4801 Parent_Kind
:= Nkind
(Parent_Node
);
4803 if Parent_Kind
= N_Qualified_Expression
then
4804 Parent_Node
:= Parent
(Parent_Node
);
4805 Parent_Kind
:= Nkind
(Parent_Node
);
4808 if Parent_Kind
= N_Aggregate
4809 or else Parent_Kind
= N_Extension_Aggregate
4810 or else Parent_Kind
= N_Component_Association
4811 or else (Parent_Kind
= N_Object_Declaration
4812 and then Needs_Finalization
(Typ
))
4813 or else (Parent_Kind
= N_Assignment_Statement
4814 and then Inside_Init_Proc
)
4816 if Static_Array_Aggregate
(N
)
4817 or else Compile_Time_Known_Aggregate
(N
)
4819 Set_Expansion_Delayed
(N
, False);
4822 Set_Expansion_Delayed
(N
);
4829 -- Look if in place aggregate expansion is possible
4831 -- For object declarations we build the aggregate in place, unless
4832 -- the array is bit-packed or the component is controlled.
4834 -- For assignments we do the assignment in place if all the component
4835 -- associations have compile-time known values. For other cases we
4836 -- create a temporary. The analysis for safety of on-line assignment
4837 -- is delicate, i.e. we don't know how to do it fully yet ???
4839 -- For allocators we assign to the designated object in place if the
4840 -- aggregate meets the same conditions as other in-place assignments.
4841 -- In this case the aggregate may not come from source but was created
4842 -- for default initialization, e.g. with Initialize_Scalars.
4844 if Requires_Transient_Scope
(Typ
) then
4845 Establish_Transient_Scope
4846 (N
, Sec_Stack
=> Has_Controlled_Component
(Typ
));
4849 if Has_Default_Init_Comps
(N
) then
4850 Maybe_In_Place_OK
:= False;
4852 elsif Is_Bit_Packed_Array
(Typ
)
4853 or else Has_Controlled_Component
(Typ
)
4855 Maybe_In_Place_OK
:= False;
4858 Maybe_In_Place_OK
:=
4859 (Nkind
(Parent
(N
)) = N_Assignment_Statement
4860 and then Comes_From_Source
(N
)
4861 and then In_Place_Assign_OK
)
4864 (Nkind
(Parent
(Parent
(N
))) = N_Allocator
4865 and then In_Place_Assign_OK
);
4868 -- If this is an array of tasks, it will be expanded into build-in-place
4869 -- assignments. Build an activation chain for the tasks now.
4871 if Has_Task
(Etype
(N
)) then
4872 Build_Activation_Chain_Entity
(N
);
4875 -- Should document these individual tests ???
4877 if not Has_Default_Init_Comps
(N
)
4878 and then Comes_From_Source
(Parent
(N
))
4879 and then Nkind
(Parent
(N
)) = N_Object_Declaration
4881 Must_Slide
(Etype
(Defining_Identifier
(Parent
(N
))), Typ
)
4882 and then N
= Expression
(Parent
(N
))
4883 and then not Is_Bit_Packed_Array
(Typ
)
4884 and then not Has_Controlled_Component
(Typ
)
4886 -- If the aggregate is the expression in an object declaration, it
4887 -- cannot be expanded in place. Lookahead in the current declarative
4888 -- part to find an address clause for the object being declared. If
4889 -- one is present, we cannot build in place. Unclear comment???
4891 and then not Has_Following_Address_Clause
(Parent
(N
))
4893 Tmp
:= Defining_Identifier
(Parent
(N
));
4894 Set_No_Initialization
(Parent
(N
));
4895 Set_Expression
(Parent
(N
), Empty
);
4897 -- Set the type of the entity, for use in the analysis of the
4898 -- subsequent indexed assignments. If the nominal type is not
4899 -- constrained, build a subtype from the known bounds of the
4900 -- aggregate. If the declaration has a subtype mark, use it,
4901 -- otherwise use the itype of the aggregate.
4903 if not Is_Constrained
(Typ
) then
4904 Build_Constrained_Type
(Positional
=> False);
4905 elsif Is_Entity_Name
(Object_Definition
(Parent
(N
)))
4906 and then Is_Constrained
(Entity
(Object_Definition
(Parent
(N
))))
4908 Set_Etype
(Tmp
, Entity
(Object_Definition
(Parent
(N
))));
4910 Set_Size_Known_At_Compile_Time
(Typ
, False);
4911 Set_Etype
(Tmp
, Typ
);
4914 elsif Maybe_In_Place_OK
4915 and then Nkind
(Parent
(N
)) = N_Qualified_Expression
4916 and then Nkind
(Parent
(Parent
(N
))) = N_Allocator
4918 Set_Expansion_Delayed
(N
);
4921 -- In the remaining cases the aggregate is the RHS of an assignment
4923 elsif Maybe_In_Place_OK
4924 and then Safe_Left_Hand_Side
(Name
(Parent
(N
)))
4926 Tmp
:= Name
(Parent
(N
));
4928 if Etype
(Tmp
) /= Etype
(N
) then
4929 Apply_Length_Check
(N
, Etype
(Tmp
));
4931 if Nkind
(N
) = N_Raise_Constraint_Error
then
4933 -- Static error, nothing further to expand
4939 elsif Maybe_In_Place_OK
4940 and then Nkind
(Name
(Parent
(N
))) = N_Slice
4941 and then Safe_Slice_Assignment
(N
)
4943 -- Safe_Slice_Assignment rewrites assignment as a loop
4949 -- In place aggregate expansion is not possible
4952 Maybe_In_Place_OK
:= False;
4953 Tmp
:= Make_Temporary
(Loc
, 'A', N
);
4955 Make_Object_Declaration
4957 Defining_Identifier
=> Tmp
,
4958 Object_Definition
=> New_Occurrence_Of
(Typ
, Loc
));
4959 Set_No_Initialization
(Tmp_Decl
, True);
4961 -- If we are within a loop, the temporary will be pushed on the
4962 -- stack at each iteration. If the aggregate is the expression for an
4963 -- allocator, it will be immediately copied to the heap and can
4964 -- be reclaimed at once. We create a transient scope around the
4965 -- aggregate for this purpose.
4967 if Ekind
(Current_Scope
) = E_Loop
4968 and then Nkind
(Parent
(Parent
(N
))) = N_Allocator
4970 Establish_Transient_Scope
(N
, False);
4973 Insert_Action
(N
, Tmp_Decl
);
4976 -- Construct and insert the aggregate code. We can safely suppress index
4977 -- checks because this code is guaranteed not to raise CE on index
4978 -- checks. However we should *not* suppress all checks.
4984 if Nkind
(Tmp
) = N_Defining_Identifier
then
4985 Target
:= New_Reference_To
(Tmp
, Loc
);
4989 if Has_Default_Init_Comps
(N
) then
4991 -- Ada 2005 (AI-287): This case has not been analyzed???
4993 raise Program_Error
;
4996 -- Name in assignment is explicit dereference
4998 Target
:= New_Copy
(Tmp
);
5002 Build_Array_Aggr_Code
(N
,
5004 Index
=> First_Index
(Typ
),
5006 Scalar_Comp
=> Is_Scalar_Type
(Ctyp
));
5009 if Comes_From_Source
(Tmp
) then
5010 Insert_Actions_After
(Parent
(N
), Aggr_Code
);
5013 Insert_Actions
(N
, Aggr_Code
);
5016 -- If the aggregate has been assigned in place, remove the original
5019 if Nkind
(Parent
(N
)) = N_Assignment_Statement
5020 and then Maybe_In_Place_OK
5022 Rewrite
(Parent
(N
), Make_Null_Statement
(Loc
));
5024 elsif Nkind
(Parent
(N
)) /= N_Object_Declaration
5025 or else Tmp
/= Defining_Identifier
(Parent
(N
))
5027 Rewrite
(N
, New_Occurrence_Of
(Tmp
, Loc
));
5028 Analyze_And_Resolve
(N
, Typ
);
5030 end Expand_Array_Aggregate
;
5032 ------------------------
5033 -- Expand_N_Aggregate --
5034 ------------------------
5036 procedure Expand_N_Aggregate
(N
: Node_Id
) is
5038 if Is_Record_Type
(Etype
(N
)) then
5039 Expand_Record_Aggregate
(N
);
5041 Expand_Array_Aggregate
(N
);
5044 when RE_Not_Available
=>
5046 end Expand_N_Aggregate
;
5048 ----------------------------------
5049 -- Expand_N_Extension_Aggregate --
5050 ----------------------------------
5052 -- If the ancestor part is an expression, add a component association for
5053 -- the parent field. If the type of the ancestor part is not the direct
5054 -- parent of the expected type, build recursively the needed ancestors.
5055 -- If the ancestor part is a subtype_mark, replace aggregate with a decla-
5056 -- ration for a temporary of the expected type, followed by individual
5057 -- assignments to the given components.
5059 procedure Expand_N_Extension_Aggregate
(N
: Node_Id
) is
5060 Loc
: constant Source_Ptr
:= Sloc
(N
);
5061 A
: constant Node_Id
:= Ancestor_Part
(N
);
5062 Typ
: constant Entity_Id
:= Etype
(N
);
5065 -- If the ancestor is a subtype mark, an init proc must be called
5066 -- on the resulting object which thus has to be materialized in
5069 if Is_Entity_Name
(A
) and then Is_Type
(Entity
(A
)) then
5070 Convert_To_Assignments
(N
, Typ
);
5072 -- The extension aggregate is transformed into a record aggregate
5073 -- of the following form (c1 and c2 are inherited components)
5075 -- (Exp with c3 => a, c4 => b)
5076 -- ==> (c1 => Exp.c1, c2 => Exp.c2, c3 => a, c4 => b)
5081 if Tagged_Type_Expansion
then
5082 Expand_Record_Aggregate
(N
,
5085 (Node
(First_Elmt
(Access_Disp_Table
(Typ
))), Loc
),
5088 -- No tag is needed in the case of a VM
5091 Expand_Record_Aggregate
(N
, Parent_Expr
=> A
);
5096 when RE_Not_Available
=>
5098 end Expand_N_Extension_Aggregate
;
5100 -----------------------------
5101 -- Expand_Record_Aggregate --
5102 -----------------------------
5104 procedure Expand_Record_Aggregate
5106 Orig_Tag
: Node_Id
:= Empty
;
5107 Parent_Expr
: Node_Id
:= Empty
)
5109 Loc
: constant Source_Ptr
:= Sloc
(N
);
5110 Comps
: constant List_Id
:= Component_Associations
(N
);
5111 Typ
: constant Entity_Id
:= Etype
(N
);
5112 Base_Typ
: constant Entity_Id
:= Base_Type
(Typ
);
5114 Static_Components
: Boolean := True;
5115 -- Flag to indicate whether all components are compile-time known,
5116 -- and the aggregate can be constructed statically and handled by
5119 function Component_Not_OK_For_Backend
return Boolean;
5120 -- Check for presence of component which makes it impossible for the
5121 -- backend to process the aggregate, thus requiring the use of a series
5122 -- of assignment statements. Cases checked for are a nested aggregate
5123 -- needing Late_Expansion, the presence of a tagged component which may
5124 -- need tag adjustment, and a bit unaligned component reference.
5126 -- We also force expansion into assignments if a component is of a
5127 -- mutable type (including a private type with discriminants) because
5128 -- in that case the size of the component to be copied may be smaller
5129 -- than the side of the target, and there is no simple way for gigi
5130 -- to compute the size of the object to be copied.
5132 -- NOTE: This is part of the ongoing work to define precisely the
5133 -- interface between front-end and back-end handling of aggregates.
5134 -- In general it is desirable to pass aggregates as they are to gigi,
5135 -- in order to minimize elaboration code. This is one case where the
5136 -- semantics of Ada complicate the analysis and lead to anomalies in
5137 -- the gcc back-end if the aggregate is not expanded into assignments.
5139 function Has_Visible_Private_Ancestor
(Id
: E
) return Boolean;
5140 -- If any ancestor of the current type is private, the aggregate
5141 -- cannot be built in place. We canot rely on Has_Private_Ancestor,
5142 -- because it will not be set when type and its parent are in the
5143 -- same scope, and the parent component needs expansion.
5145 function Top_Level_Aggregate
(N
: Node_Id
) return Node_Id
;
5146 -- For nested aggregates return the ultimate enclosing aggregate; for
5147 -- non-nested aggregates return N.
5149 ----------------------------------
5150 -- Component_Not_OK_For_Backend --
5151 ----------------------------------
5153 function Component_Not_OK_For_Backend
return Boolean is
5163 while Present
(C
) loop
5165 -- If the component has box initialization, expansion is needed
5166 -- and component is not ready for backend.
5168 if Box_Present
(C
) then
5172 if Nkind
(Expression
(C
)) = N_Qualified_Expression
then
5173 Expr_Q
:= Expression
(Expression
(C
));
5175 Expr_Q
:= Expression
(C
);
5178 -- Return true if the aggregate has any associations for tagged
5179 -- components that may require tag adjustment.
5181 -- These are cases where the source expression may have a tag that
5182 -- could differ from the component tag (e.g., can occur for type
5183 -- conversions and formal parameters). (Tag adjustment not needed
5184 -- if VM_Target because object tags are implicit in the machine.)
5186 if Is_Tagged_Type
(Etype
(Expr_Q
))
5187 and then (Nkind
(Expr_Q
) = N_Type_Conversion
5188 or else (Is_Entity_Name
(Expr_Q
)
5190 Ekind
(Entity
(Expr_Q
)) in Formal_Kind
))
5191 and then Tagged_Type_Expansion
5193 Static_Components
:= False;
5196 elsif Is_Delayed_Aggregate
(Expr_Q
) then
5197 Static_Components
:= False;
5200 elsif Possible_Bit_Aligned_Component
(Expr_Q
) then
5201 Static_Components
:= False;
5205 if Is_Scalar_Type
(Etype
(Expr_Q
)) then
5206 if not Compile_Time_Known_Value
(Expr_Q
) then
5207 Static_Components
:= False;
5210 elsif Nkind
(Expr_Q
) /= N_Aggregate
5211 or else not Compile_Time_Known_Aggregate
(Expr_Q
)
5213 Static_Components
:= False;
5215 if Is_Private_Type
(Etype
(Expr_Q
))
5216 and then Has_Discriminants
(Etype
(Expr_Q
))
5226 end Component_Not_OK_For_Backend
;
5228 -----------------------------------
5229 -- Has_Visible_Private_Ancestor --
5230 -----------------------------------
5232 function Has_Visible_Private_Ancestor
(Id
: E
) return Boolean is
5233 R
: constant Entity_Id
:= Root_Type
(Id
);
5234 T1
: Entity_Id
:= Id
;
5238 if Is_Private_Type
(T1
) then
5248 end Has_Visible_Private_Ancestor
;
5250 -------------------------
5251 -- Top_Level_Aggregate --
5252 -------------------------
5254 function Top_Level_Aggregate
(N
: Node_Id
) return Node_Id
is
5259 while Present
(Parent
(Aggr
))
5260 and then Nkind_In
(Parent
(Aggr
), N_Component_Association
,
5263 Aggr
:= Parent
(Aggr
);
5267 end Top_Level_Aggregate
;
5271 Top_Level_Aggr
: constant Node_Id
:= Top_Level_Aggregate
(N
);
5272 Tag_Value
: Node_Id
;
5276 -- Start of processing for Expand_Record_Aggregate
5279 -- If the aggregate is to be assigned to an atomic variable, we
5280 -- have to prevent a piecemeal assignment even if the aggregate
5281 -- is to be expanded. We create a temporary for the aggregate, and
5282 -- assign the temporary instead, so that the back end can generate
5283 -- an atomic move for it.
5286 and then Comes_From_Source
(Parent
(N
))
5287 and then Is_Atomic_Aggregate
(N
, Typ
)
5291 -- No special management required for aggregates used to initialize
5292 -- statically allocated dispatch tables
5294 elsif Is_Static_Dispatch_Table_Aggregate
(N
) then
5298 -- Ada 2005 (AI-318-2): We need to convert to assignments if components
5299 -- are build-in-place function calls. The assignments will each turn
5300 -- into a build-in-place function call. If components are all static,
5301 -- we can pass the aggregate to the backend regardless of limitedness.
5303 -- Extension aggregates, aggregates in extended return statements, and
5304 -- aggregates for C++ imported types must be expanded.
5306 if Ada_Version
>= Ada_2005
and then Is_Immutably_Limited_Type
(Typ
) then
5307 if not Nkind_In
(Parent
(N
), N_Object_Declaration
,
5308 N_Component_Association
)
5310 Convert_To_Assignments
(N
, Typ
);
5312 elsif Nkind
(N
) = N_Extension_Aggregate
5313 or else Convention
(Typ
) = Convention_CPP
5315 Convert_To_Assignments
(N
, Typ
);
5317 elsif not Size_Known_At_Compile_Time
(Typ
)
5318 or else Component_Not_OK_For_Backend
5319 or else not Static_Components
5321 Convert_To_Assignments
(N
, Typ
);
5324 Set_Compile_Time_Known_Aggregate
(N
);
5325 Set_Expansion_Delayed
(N
, False);
5328 -- Gigi doesn't properly handle temporaries of variable size so we
5329 -- generate it in the front-end
5331 elsif not Size_Known_At_Compile_Time
(Typ
)
5332 and then Tagged_Type_Expansion
5334 Convert_To_Assignments
(N
, Typ
);
5336 -- Temporaries for controlled aggregates need to be attached to a final
5337 -- chain in order to be properly finalized, so it has to be created in
5340 elsif Is_Controlled
(Typ
)
5341 or else Has_Controlled_Component
(Base_Type
(Typ
))
5343 Convert_To_Assignments
(N
, Typ
);
5345 -- Ada 2005 (AI-287): In case of default initialized components we
5346 -- convert the aggregate into assignments.
5348 elsif Has_Default_Init_Comps
(N
) then
5349 Convert_To_Assignments
(N
, Typ
);
5353 elsif Component_Not_OK_For_Backend
then
5354 Convert_To_Assignments
(N
, Typ
);
5356 -- If an ancestor is private, some components are not inherited and
5357 -- we cannot expand into a record aggregate
5359 elsif Has_Visible_Private_Ancestor
(Typ
) then
5360 Convert_To_Assignments
(N
, Typ
);
5362 -- ??? The following was done to compile fxacc00.ads in the ACVCs. Gigi
5363 -- is not able to handle the aggregate for Late_Request.
5365 elsif Is_Tagged_Type
(Typ
) and then Has_Discriminants
(Typ
) then
5366 Convert_To_Assignments
(N
, Typ
);
5368 -- If the tagged types covers interface types we need to initialize all
5369 -- hidden components containing pointers to secondary dispatch tables.
5371 elsif Is_Tagged_Type
(Typ
) and then Has_Interfaces
(Typ
) then
5372 Convert_To_Assignments
(N
, Typ
);
5374 -- If some components are mutable, the size of the aggregate component
5375 -- may be distinct from the default size of the type component, so
5376 -- we need to expand to insure that the back-end copies the proper
5377 -- size of the data. However, if the aggregate is the initial value of
5378 -- a constant, the target is immutable and may be built statically.
5380 elsif Has_Mutable_Components
(Typ
)
5382 (Nkind
(Parent
(Top_Level_Aggr
)) /= N_Object_Declaration
5383 or else not Constant_Present
(Parent
(Top_Level_Aggr
)))
5385 Convert_To_Assignments
(N
, Typ
);
5387 -- If the type involved has any non-bit aligned components, then we are
5388 -- not sure that the back end can handle this case correctly.
5390 elsif Type_May_Have_Bit_Aligned_Components
(Typ
) then
5391 Convert_To_Assignments
(N
, Typ
);
5393 -- In all other cases, build a proper aggregate handlable by gigi
5396 if Nkind
(N
) = N_Aggregate
then
5398 -- If the aggregate is static and can be handled by the back-end,
5399 -- nothing left to do.
5401 if Static_Components
then
5402 Set_Compile_Time_Known_Aggregate
(N
);
5403 Set_Expansion_Delayed
(N
, False);
5407 -- If no discriminants, nothing special to do
5409 if not Has_Discriminants
(Typ
) then
5412 -- Case of discriminants present
5414 elsif Is_Derived_Type
(Typ
) then
5416 -- For untagged types, non-stored discriminants are replaced
5417 -- with stored discriminants, which are the ones that gigi uses
5418 -- to describe the type and its components.
5420 Generate_Aggregate_For_Derived_Type
: declare
5421 Constraints
: constant List_Id
:= New_List
;
5422 First_Comp
: Node_Id
;
5423 Discriminant
: Entity_Id
;
5425 Num_Disc
: Int
:= 0;
5426 Num_Gird
: Int
:= 0;
5428 procedure Prepend_Stored_Values
(T
: Entity_Id
);
5429 -- Scan the list of stored discriminants of the type, and add
5430 -- their values to the aggregate being built.
5432 ---------------------------
5433 -- Prepend_Stored_Values --
5434 ---------------------------
5436 procedure Prepend_Stored_Values
(T
: Entity_Id
) is
5438 Discriminant
:= First_Stored_Discriminant
(T
);
5439 while Present
(Discriminant
) loop
5441 Make_Component_Association
(Loc
,
5443 New_List
(New_Occurrence_Of
(Discriminant
, Loc
)),
5447 Get_Discriminant_Value
(
5450 Discriminant_Constraint
(Typ
))));
5452 if No
(First_Comp
) then
5453 Prepend_To
(Component_Associations
(N
), New_Comp
);
5455 Insert_After
(First_Comp
, New_Comp
);
5458 First_Comp
:= New_Comp
;
5459 Next_Stored_Discriminant
(Discriminant
);
5461 end Prepend_Stored_Values
;
5463 -- Start of processing for Generate_Aggregate_For_Derived_Type
5466 -- Remove the associations for the discriminant of derived type
5468 First_Comp
:= First
(Component_Associations
(N
));
5469 while Present
(First_Comp
) loop
5474 (First
(Choices
(Comp
)))) = E_Discriminant
5477 Num_Disc
:= Num_Disc
+ 1;
5481 -- Insert stored discriminant associations in the correct
5482 -- order. If there are more stored discriminants than new
5483 -- discriminants, there is at least one new discriminant that
5484 -- constrains more than one of the stored discriminants. In
5485 -- this case we need to construct a proper subtype of the
5486 -- parent type, in order to supply values to all the
5487 -- components. Otherwise there is one-one correspondence
5488 -- between the constraints and the stored discriminants.
5490 First_Comp
:= Empty
;
5492 Discriminant
:= First_Stored_Discriminant
(Base_Type
(Typ
));
5493 while Present
(Discriminant
) loop
5494 Num_Gird
:= Num_Gird
+ 1;
5495 Next_Stored_Discriminant
(Discriminant
);
5498 -- Case of more stored discriminants than new discriminants
5500 if Num_Gird
> Num_Disc
then
5502 -- Create a proper subtype of the parent type, which is the
5503 -- proper implementation type for the aggregate, and convert
5504 -- it to the intended target type.
5506 Discriminant
:= First_Stored_Discriminant
(Base_Type
(Typ
));
5507 while Present
(Discriminant
) loop
5510 Get_Discriminant_Value
(
5513 Discriminant_Constraint
(Typ
)));
5514 Append
(New_Comp
, Constraints
);
5515 Next_Stored_Discriminant
(Discriminant
);
5519 Make_Subtype_Declaration
(Loc
,
5520 Defining_Identifier
=> Make_Temporary
(Loc
, 'T'),
5521 Subtype_Indication
=>
5522 Make_Subtype_Indication
(Loc
,
5524 New_Occurrence_Of
(Etype
(Base_Type
(Typ
)), Loc
),
5526 Make_Index_Or_Discriminant_Constraint
5527 (Loc
, Constraints
)));
5529 Insert_Action
(N
, Decl
);
5530 Prepend_Stored_Values
(Base_Type
(Typ
));
5532 Set_Etype
(N
, Defining_Identifier
(Decl
));
5535 Rewrite
(N
, Unchecked_Convert_To
(Typ
, N
));
5538 -- Case where we do not have fewer new discriminants than
5539 -- stored discriminants, so in this case we can simply use the
5540 -- stored discriminants of the subtype.
5543 Prepend_Stored_Values
(Typ
);
5545 end Generate_Aggregate_For_Derived_Type
;
5548 if Is_Tagged_Type
(Typ
) then
5550 -- The tagged case, _parent and _tag component must be created
5552 -- Reset null_present unconditionally. tagged records always have
5553 -- at least one field (the tag or the parent)
5555 Set_Null_Record_Present
(N
, False);
5557 -- When the current aggregate comes from the expansion of an
5558 -- extension aggregate, the parent expr is replaced by an
5559 -- aggregate formed by selected components of this expr
5561 if Present
(Parent_Expr
)
5562 and then Is_Empty_List
(Comps
)
5564 Comp
:= First_Component_Or_Discriminant
(Typ
);
5565 while Present
(Comp
) loop
5567 -- Skip all expander-generated components
5570 not Comes_From_Source
(Original_Record_Component
(Comp
))
5576 Make_Selected_Component
(Loc
,
5578 Unchecked_Convert_To
(Typ
,
5579 Duplicate_Subexpr
(Parent_Expr
, True)),
5581 Selector_Name
=> New_Occurrence_Of
(Comp
, Loc
));
5584 Make_Component_Association
(Loc
,
5586 New_List
(New_Occurrence_Of
(Comp
, Loc
)),
5590 Analyze_And_Resolve
(New_Comp
, Etype
(Comp
));
5593 Next_Component_Or_Discriminant
(Comp
);
5597 -- Compute the value for the Tag now, if the type is a root it
5598 -- will be included in the aggregate right away, otherwise it will
5599 -- be propagated to the parent aggregate
5601 if Present
(Orig_Tag
) then
5602 Tag_Value
:= Orig_Tag
;
5603 elsif not Tagged_Type_Expansion
then
5608 (Node
(First_Elmt
(Access_Disp_Table
(Typ
))), Loc
);
5611 -- For a derived type, an aggregate for the parent is formed with
5612 -- all the inherited components.
5614 if Is_Derived_Type
(Typ
) then
5617 First_Comp
: Node_Id
;
5618 Parent_Comps
: List_Id
;
5619 Parent_Aggr
: Node_Id
;
5620 Parent_Name
: Node_Id
;
5623 -- Remove the inherited component association from the
5624 -- aggregate and store them in the parent aggregate
5626 First_Comp
:= First
(Component_Associations
(N
));
5627 Parent_Comps
:= New_List
;
5628 while Present
(First_Comp
)
5629 and then Scope
(Original_Record_Component
(
5630 Entity
(First
(Choices
(First_Comp
))))) /= Base_Typ
5635 Append
(Comp
, Parent_Comps
);
5638 Parent_Aggr
:= Make_Aggregate
(Loc
,
5639 Component_Associations
=> Parent_Comps
);
5640 Set_Etype
(Parent_Aggr
, Etype
(Base_Type
(Typ
)));
5642 -- Find the _parent component
5644 Comp
:= First_Component
(Typ
);
5645 while Chars
(Comp
) /= Name_uParent
loop
5646 Comp
:= Next_Component
(Comp
);
5649 Parent_Name
:= New_Occurrence_Of
(Comp
, Loc
);
5651 -- Insert the parent aggregate
5653 Prepend_To
(Component_Associations
(N
),
5654 Make_Component_Association
(Loc
,
5655 Choices
=> New_List
(Parent_Name
),
5656 Expression
=> Parent_Aggr
));
5658 -- Expand recursively the parent propagating the right Tag
5660 Expand_Record_Aggregate
(
5661 Parent_Aggr
, Tag_Value
, Parent_Expr
);
5664 -- For a root type, the tag component is added (unless compiling
5665 -- for the VMs, where tags are implicit).
5667 elsif Tagged_Type_Expansion
then
5669 Tag_Name
: constant Node_Id
:=
5671 (First_Tag_Component
(Typ
), Loc
);
5672 Typ_Tag
: constant Entity_Id
:= RTE
(RE_Tag
);
5673 Conv_Node
: constant Node_Id
:=
5674 Unchecked_Convert_To
(Typ_Tag
, Tag_Value
);
5677 Set_Etype
(Conv_Node
, Typ_Tag
);
5678 Prepend_To
(Component_Associations
(N
),
5679 Make_Component_Association
(Loc
,
5680 Choices
=> New_List
(Tag_Name
),
5681 Expression
=> Conv_Node
));
5687 end Expand_Record_Aggregate
;
5689 ----------------------------
5690 -- Has_Default_Init_Comps --
5691 ----------------------------
5693 function Has_Default_Init_Comps
(N
: Node_Id
) return Boolean is
5694 Comps
: constant List_Id
:= Component_Associations
(N
);
5698 pragma Assert
(Nkind_In
(N
, N_Aggregate
, N_Extension_Aggregate
));
5704 if Has_Self_Reference
(N
) then
5708 -- Check if any direct component has default initialized components
5711 while Present
(C
) loop
5712 if Box_Present
(C
) then
5719 -- Recursive call in case of aggregate expression
5722 while Present
(C
) loop
5723 Expr
:= Expression
(C
);
5727 Nkind_In
(Expr
, N_Aggregate
, N_Extension_Aggregate
)
5728 and then Has_Default_Init_Comps
(Expr
)
5737 end Has_Default_Init_Comps
;
5739 --------------------------
5740 -- Is_Delayed_Aggregate --
5741 --------------------------
5743 function Is_Delayed_Aggregate
(N
: Node_Id
) return Boolean is
5744 Node
: Node_Id
:= N
;
5745 Kind
: Node_Kind
:= Nkind
(Node
);
5748 if Kind
= N_Qualified_Expression
then
5749 Node
:= Expression
(Node
);
5750 Kind
:= Nkind
(Node
);
5753 if Kind
/= N_Aggregate
and then Kind
/= N_Extension_Aggregate
then
5756 return Expansion_Delayed
(Node
);
5758 end Is_Delayed_Aggregate
;
5760 ----------------------------------------
5761 -- Is_Static_Dispatch_Table_Aggregate --
5762 ----------------------------------------
5764 function Is_Static_Dispatch_Table_Aggregate
(N
: Node_Id
) return Boolean is
5765 Typ
: constant Entity_Id
:= Base_Type
(Etype
(N
));
5768 return Static_Dispatch_Tables
5769 and then Tagged_Type_Expansion
5770 and then RTU_Loaded
(Ada_Tags
)
5772 -- Avoid circularity when rebuilding the compiler
5774 and then Cunit_Entity
(Get_Source_Unit
(N
)) /= RTU_Entity
(Ada_Tags
)
5775 and then (Typ
= RTE
(RE_Dispatch_Table_Wrapper
)
5777 Typ
= RTE
(RE_Address_Array
)
5779 Typ
= RTE
(RE_Type_Specific_Data
)
5781 Typ
= RTE
(RE_Tag_Table
)
5783 (RTE_Available
(RE_Interface_Data
)
5784 and then Typ
= RTE
(RE_Interface_Data
))
5786 (RTE_Available
(RE_Interfaces_Array
)
5787 and then Typ
= RTE
(RE_Interfaces_Array
))
5789 (RTE_Available
(RE_Interface_Data_Element
)
5790 and then Typ
= RTE
(RE_Interface_Data_Element
)));
5791 end Is_Static_Dispatch_Table_Aggregate
;
5793 --------------------
5794 -- Late_Expansion --
5795 --------------------
5797 function Late_Expansion
5800 Target
: Node_Id
) return List_Id
5803 if Is_Record_Type
(Etype
(N
)) then
5804 return Build_Record_Aggr_Code
(N
, Typ
, Target
);
5806 else pragma Assert
(Is_Array_Type
(Etype
(N
)));
5808 Build_Array_Aggr_Code
5810 Ctype
=> Component_Type
(Etype
(N
)),
5811 Index
=> First_Index
(Typ
),
5813 Scalar_Comp
=> Is_Scalar_Type
(Component_Type
(Typ
)),
5814 Indexes
=> No_List
);
5818 ----------------------------------
5819 -- Make_OK_Assignment_Statement --
5820 ----------------------------------
5822 function Make_OK_Assignment_Statement
5825 Expression
: Node_Id
) return Node_Id
5828 Set_Assignment_OK
(Name
);
5830 return Make_Assignment_Statement
(Sloc
, Name
, Expression
);
5831 end Make_OK_Assignment_Statement
;
5833 -----------------------
5834 -- Number_Of_Choices --
5835 -----------------------
5837 function Number_Of_Choices
(N
: Node_Id
) return Nat
is
5841 Nb_Choices
: Nat
:= 0;
5844 if Present
(Expressions
(N
)) then
5848 Assoc
:= First
(Component_Associations
(N
));
5849 while Present
(Assoc
) loop
5850 Choice
:= First
(Choices
(Assoc
));
5851 while Present
(Choice
) loop
5852 if Nkind
(Choice
) /= N_Others_Choice
then
5853 Nb_Choices
:= Nb_Choices
+ 1;
5863 end Number_Of_Choices
;
5865 ------------------------------------
5866 -- Packed_Array_Aggregate_Handled --
5867 ------------------------------------
5869 -- The current version of this procedure will handle at compile time
5870 -- any array aggregate that meets these conditions:
5872 -- One dimensional, bit packed
5873 -- Underlying packed type is modular type
5874 -- Bounds are within 32-bit Int range
5875 -- All bounds and values are static
5877 function Packed_Array_Aggregate_Handled
(N
: Node_Id
) return Boolean is
5878 Loc
: constant Source_Ptr
:= Sloc
(N
);
5879 Typ
: constant Entity_Id
:= Etype
(N
);
5880 Ctyp
: constant Entity_Id
:= Component_Type
(Typ
);
5882 Not_Handled
: exception;
5883 -- Exception raised if this aggregate cannot be handled
5886 -- For now, handle only one dimensional bit packed arrays
5888 if not Is_Bit_Packed_Array
(Typ
)
5889 or else Number_Dimensions
(Typ
) > 1
5890 or else not Is_Modular_Integer_Type
(Packed_Array_Type
(Typ
))
5895 if not Is_Scalar_Type
(Component_Type
(Typ
))
5896 and then Has_Non_Standard_Rep
(Component_Type
(Typ
))
5902 Csiz
: constant Nat
:= UI_To_Int
(Component_Size
(Typ
));
5906 -- Bounds of index type
5910 -- Values of bounds if compile time known
5912 function Get_Component_Val
(N
: Node_Id
) return Uint
;
5913 -- Given a expression value N of the component type Ctyp, returns a
5914 -- value of Csiz (component size) bits representing this value. If
5915 -- the value is non-static or any other reason exists why the value
5916 -- cannot be returned, then Not_Handled is raised.
5918 -----------------------
5919 -- Get_Component_Val --
5920 -----------------------
5922 function Get_Component_Val
(N
: Node_Id
) return Uint
is
5926 -- We have to analyze the expression here before doing any further
5927 -- processing here. The analysis of such expressions is deferred
5928 -- till expansion to prevent some problems of premature analysis.
5930 Analyze_And_Resolve
(N
, Ctyp
);
5932 -- Must have a compile time value. String literals have to be
5933 -- converted into temporaries as well, because they cannot easily
5934 -- be converted into their bit representation.
5936 if not Compile_Time_Known_Value
(N
)
5937 or else Nkind
(N
) = N_String_Literal
5942 Val
:= Expr_Rep_Value
(N
);
5944 -- Adjust for bias, and strip proper number of bits
5946 if Has_Biased_Representation
(Ctyp
) then
5947 Val
:= Val
- Expr_Value
(Type_Low_Bound
(Ctyp
));
5950 return Val
mod Uint_2
** Csiz
;
5951 end Get_Component_Val
;
5953 -- Here we know we have a one dimensional bit packed array
5956 Get_Index_Bounds
(First_Index
(Typ
), Lo
, Hi
);
5958 -- Cannot do anything if bounds are dynamic
5960 if not Compile_Time_Known_Value
(Lo
)
5962 not Compile_Time_Known_Value
(Hi
)
5967 -- Or are silly out of range of int bounds
5969 Lob
:= Expr_Value
(Lo
);
5970 Hib
:= Expr_Value
(Hi
);
5972 if not UI_Is_In_Int_Range
(Lob
)
5974 not UI_Is_In_Int_Range
(Hib
)
5979 -- At this stage we have a suitable aggregate for handling at compile
5980 -- time (the only remaining checks are that the values of expressions
5981 -- in the aggregate are compile time known (check is performed by
5982 -- Get_Component_Val), and that any subtypes or ranges are statically
5985 -- If the aggregate is not fully positional at this stage, then
5986 -- convert it to positional form. Either this will fail, in which
5987 -- case we can do nothing, or it will succeed, in which case we have
5988 -- succeeded in handling the aggregate, or it will stay an aggregate,
5989 -- in which case we have failed to handle this case.
5991 if Present
(Component_Associations
(N
)) then
5992 Convert_To_Positional
5993 (N
, Max_Others_Replicate
=> 64, Handle_Bit_Packed
=> True);
5994 return Nkind
(N
) /= N_Aggregate
;
5997 -- Otherwise we are all positional, so convert to proper value
6000 Lov
: constant Int
:= UI_To_Int
(Lob
);
6001 Hiv
: constant Int
:= UI_To_Int
(Hib
);
6003 Len
: constant Nat
:= Int
'Max (0, Hiv
- Lov
+ 1);
6004 -- The length of the array (number of elements)
6006 Aggregate_Val
: Uint
;
6007 -- Value of aggregate. The value is set in the low order bits of
6008 -- this value. For the little-endian case, the values are stored
6009 -- from low-order to high-order and for the big-endian case the
6010 -- values are stored from high-order to low-order. Note that gigi
6011 -- will take care of the conversions to left justify the value in
6012 -- the big endian case (because of left justified modular type
6013 -- processing), so we do not have to worry about that here.
6016 -- Integer literal for resulting constructed value
6019 -- Shift count from low order for next value
6022 -- Shift increment for loop
6025 -- Next expression from positional parameters of aggregate
6028 -- For little endian, we fill up the low order bits of the target
6029 -- value. For big endian we fill up the high order bits of the
6030 -- target value (which is a left justified modular value).
6032 if Bytes_Big_Endian
xor Debug_Flag_8
then
6033 Shift
:= Csiz
* (Len
- 1);
6040 -- Loop to set the values
6043 Aggregate_Val
:= Uint_0
;
6045 Expr
:= First
(Expressions
(N
));
6046 Aggregate_Val
:= Get_Component_Val
(Expr
) * Uint_2
** Shift
;
6048 for J
in 2 .. Len
loop
6049 Shift
:= Shift
+ Incr
;
6052 Aggregate_Val
+ Get_Component_Val
(Expr
) * Uint_2
** Shift
;
6056 -- Now we can rewrite with the proper value
6059 Make_Integer_Literal
(Loc
,
6060 Intval
=> Aggregate_Val
);
6061 Set_Print_In_Hex
(Lit
);
6063 -- Construct the expression using this literal. Note that it is
6064 -- important to qualify the literal with its proper modular type
6065 -- since universal integer does not have the required range and
6066 -- also this is a left justified modular type, which is important
6067 -- in the big-endian case.
6070 Unchecked_Convert_To
(Typ
,
6071 Make_Qualified_Expression
(Loc
,
6073 New_Occurrence_Of
(Packed_Array_Type
(Typ
), Loc
),
6074 Expression
=> Lit
)));
6076 Analyze_And_Resolve
(N
, Typ
);
6084 end Packed_Array_Aggregate_Handled
;
6086 ----------------------------
6087 -- Has_Mutable_Components --
6088 ----------------------------
6090 function Has_Mutable_Components
(Typ
: Entity_Id
) return Boolean is
6094 Comp
:= First_Component
(Typ
);
6095 while Present
(Comp
) loop
6096 if Is_Record_Type
(Etype
(Comp
))
6097 and then Has_Discriminants
(Etype
(Comp
))
6098 and then not Is_Constrained
(Etype
(Comp
))
6103 Next_Component
(Comp
);
6107 end Has_Mutable_Components
;
6109 ------------------------------
6110 -- Initialize_Discriminants --
6111 ------------------------------
6113 procedure Initialize_Discriminants
(N
: Node_Id
; Typ
: Entity_Id
) is
6114 Loc
: constant Source_Ptr
:= Sloc
(N
);
6115 Bas
: constant Entity_Id
:= Base_Type
(Typ
);
6116 Par
: constant Entity_Id
:= Etype
(Bas
);
6117 Decl
: constant Node_Id
:= Parent
(Par
);
6121 if Is_Tagged_Type
(Bas
)
6122 and then Is_Derived_Type
(Bas
)
6123 and then Has_Discriminants
(Par
)
6124 and then Has_Discriminants
(Bas
)
6125 and then Number_Discriminants
(Bas
) /= Number_Discriminants
(Par
)
6126 and then Nkind
(Decl
) = N_Full_Type_Declaration
6127 and then Nkind
(Type_Definition
(Decl
)) = N_Record_Definition
6129 (Variant_Part
(Component_List
(Type_Definition
(Decl
))))
6130 and then Nkind
(N
) /= N_Extension_Aggregate
6133 -- Call init proc to set discriminants.
6134 -- There should eventually be a special procedure for this ???
6136 Ref
:= New_Reference_To
(Defining_Identifier
(N
), Loc
);
6137 Insert_Actions_After
(N
,
6138 Build_Initialization_Call
(Sloc
(N
), Ref
, Typ
));
6140 end Initialize_Discriminants
;
6147 (Obj_Type
: Entity_Id
;
6148 Typ
: Entity_Id
) return Boolean
6150 L1
, L2
, H1
, H2
: Node_Id
;
6152 -- No sliding if the type of the object is not established yet, if it is
6153 -- an unconstrained type whose actual subtype comes from the aggregate,
6154 -- or if the two types are identical.
6156 if not Is_Array_Type
(Obj_Type
) then
6159 elsif not Is_Constrained
(Obj_Type
) then
6162 elsif Typ
= Obj_Type
then
6166 -- Sliding can only occur along the first dimension
6168 Get_Index_Bounds
(First_Index
(Typ
), L1
, H1
);
6169 Get_Index_Bounds
(First_Index
(Obj_Type
), L2
, H2
);
6171 if not Is_Static_Expression
(L1
)
6172 or else not Is_Static_Expression
(L2
)
6173 or else not Is_Static_Expression
(H1
)
6174 or else not Is_Static_Expression
(H2
)
6178 return Expr_Value
(L1
) /= Expr_Value
(L2
)
6179 or else Expr_Value
(H1
) /= Expr_Value
(H2
);
6184 ---------------------------
6185 -- Safe_Slice_Assignment --
6186 ---------------------------
6188 function Safe_Slice_Assignment
(N
: Node_Id
) return Boolean is
6189 Loc
: constant Source_Ptr
:= Sloc
(Parent
(N
));
6190 Pref
: constant Node_Id
:= Prefix
(Name
(Parent
(N
)));
6191 Range_Node
: constant Node_Id
:= Discrete_Range
(Name
(Parent
(N
)));
6199 -- Generate: for J in Range loop Pref (J) := Expr; end loop;
6201 if Comes_From_Source
(N
)
6202 and then No
(Expressions
(N
))
6203 and then Nkind
(First
(Choices
(First
(Component_Associations
(N
)))))
6206 Expr
:= Expression
(First
(Component_Associations
(N
)));
6207 L_J
:= Make_Temporary
(Loc
, 'J');
6210 Make_Iteration_Scheme
(Loc
,
6211 Loop_Parameter_Specification
=>
6212 Make_Loop_Parameter_Specification
6214 Defining_Identifier
=> L_J
,
6215 Discrete_Subtype_Definition
=> Relocate_Node
(Range_Node
)));
6218 Make_Assignment_Statement
(Loc
,
6220 Make_Indexed_Component
(Loc
,
6221 Prefix
=> Relocate_Node
(Pref
),
6222 Expressions
=> New_List
(New_Occurrence_Of
(L_J
, Loc
))),
6223 Expression
=> Relocate_Node
(Expr
));
6225 -- Construct the final loop
6228 Make_Implicit_Loop_Statement
6229 (Node
=> Parent
(N
),
6230 Identifier
=> Empty
,
6231 Iteration_Scheme
=> L_Iter
,
6232 Statements
=> New_List
(L_Body
));
6234 -- Set type of aggregate to be type of lhs in assignment,
6235 -- to suppress redundant length checks.
6237 Set_Etype
(N
, Etype
(Name
(Parent
(N
))));
6239 Rewrite
(Parent
(N
), Stat
);
6240 Analyze
(Parent
(N
));
6246 end Safe_Slice_Assignment
;
6248 ---------------------
6249 -- Sort_Case_Table --
6250 ---------------------
6252 procedure Sort_Case_Table
(Case_Table
: in out Case_Table_Type
) is
6253 L
: constant Int
:= Case_Table
'First;
6254 U
: constant Int
:= Case_Table
'Last;
6262 T
:= Case_Table
(K
+ 1);
6266 and then Expr_Value
(Case_Table
(J
- 1).Choice_Lo
) >
6267 Expr_Value
(T
.Choice_Lo
)
6269 Case_Table
(J
) := Case_Table
(J
- 1);
6273 Case_Table
(J
) := T
;
6276 end Sort_Case_Table
;
6278 ----------------------------
6279 -- Static_Array_Aggregate --
6280 ----------------------------
6282 function Static_Array_Aggregate
(N
: Node_Id
) return Boolean is
6283 Bounds
: constant Node_Id
:= Aggregate_Bounds
(N
);
6285 Typ
: constant Entity_Id
:= Etype
(N
);
6286 Comp_Type
: constant Entity_Id
:= Component_Type
(Typ
);
6293 if Is_Tagged_Type
(Typ
)
6294 or else Is_Controlled
(Typ
)
6295 or else Is_Packed
(Typ
)
6301 and then Nkind
(Bounds
) = N_Range
6302 and then Nkind
(Low_Bound
(Bounds
)) = N_Integer_Literal
6303 and then Nkind
(High_Bound
(Bounds
)) = N_Integer_Literal
6305 Lo
:= Low_Bound
(Bounds
);
6306 Hi
:= High_Bound
(Bounds
);
6308 if No
(Component_Associations
(N
)) then
6310 -- Verify that all components are static integers
6312 Expr
:= First
(Expressions
(N
));
6313 while Present
(Expr
) loop
6314 if Nkind
(Expr
) /= N_Integer_Literal
then
6324 -- We allow only a single named association, either a static
6325 -- range or an others_clause, with a static expression.
6327 Expr
:= First
(Component_Associations
(N
));
6329 if Present
(Expressions
(N
)) then
6332 elsif Present
(Next
(Expr
)) then
6335 elsif Present
(Next
(First
(Choices
(Expr
)))) then
6339 -- The aggregate is static if all components are literals,
6340 -- or else all its components are static aggregates for the
6341 -- component type. We also limit the size of a static aggregate
6342 -- to prevent runaway static expressions.
6344 if Is_Array_Type
(Comp_Type
)
6345 or else Is_Record_Type
(Comp_Type
)
6347 if Nkind
(Expression
(Expr
)) /= N_Aggregate
6349 not Compile_Time_Known_Aggregate
(Expression
(Expr
))
6354 elsif Nkind
(Expression
(Expr
)) /= N_Integer_Literal
then
6358 if not Aggr_Size_OK
(N
, Typ
) then
6362 -- Create a positional aggregate with the right number of
6363 -- copies of the expression.
6365 Agg
:= Make_Aggregate
(Sloc
(N
), New_List
, No_List
);
6367 for I
in UI_To_Int
(Intval
(Lo
)) .. UI_To_Int
(Intval
(Hi
))
6370 (Expressions
(Agg
), New_Copy
(Expression
(Expr
)));
6372 -- The copied expression must be analyzed and resolved.
6373 -- Besides setting the type, this ensures that static
6374 -- expressions are appropriately marked as such.
6377 (Last
(Expressions
(Agg
)), Component_Type
(Typ
));
6380 Set_Aggregate_Bounds
(Agg
, Bounds
);
6381 Set_Etype
(Agg
, Typ
);
6384 Set_Compile_Time_Known_Aggregate
(N
);
6393 end Static_Array_Aggregate
;