1 ------------------------------------------------------------------------------
3 -- GNAT COMPILER COMPONENTS --
9 -- Copyright (C) 1992-2005 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 2, 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 COPYING. If not, write --
19 -- to the Free Software Foundation, 59 Temple Place - Suite 330, Boston, --
20 -- MA 02111-1307, USA. --
22 -- GNAT was originally developed by the GNAT team at New York University. --
23 -- Extensive contributions were provided by Ada Core Technologies Inc. --
25 ------------------------------------------------------------------------------
27 with Atree
; use Atree
;
28 with Checks
; use Checks
;
29 with Debug
; use Debug
;
30 with Einfo
; use Einfo
;
31 with Elists
; use Elists
;
32 with Expander
; use Expander
;
33 with Exp_Util
; use Exp_Util
;
34 with Exp_Ch3
; use Exp_Ch3
;
35 with Exp_Ch7
; use Exp_Ch7
;
36 with Exp_Ch9
; use Exp_Ch9
;
37 with Exp_Tss
; use Exp_Tss
;
38 with Freeze
; use Freeze
;
39 with Hostparm
; use Hostparm
;
40 with Itypes
; use Itypes
;
42 with Nmake
; use Nmake
;
43 with Nlists
; use Nlists
;
44 with Restrict
; use Restrict
;
45 with Rident
; use Rident
;
46 with Rtsfind
; use Rtsfind
;
47 with Ttypes
; use Ttypes
;
49 with Sem_Ch3
; use Sem_Ch3
;
50 with Sem_Eval
; use Sem_Eval
;
51 with Sem_Res
; use Sem_Res
;
52 with Sem_Util
; use Sem_Util
;
53 with Sinfo
; use Sinfo
;
54 with Snames
; use Snames
;
55 with Stand
; use Stand
;
56 with Tbuild
; use Tbuild
;
57 with Uintp
; use Uintp
;
59 package body Exp_Aggr
is
61 type Case_Bounds
is record
64 Choice_Node
: Node_Id
;
67 type Case_Table_Type
is array (Nat
range <>) of Case_Bounds
;
68 -- Table type used by Check_Case_Choices procedure
71 (Obj_Type
: Entity_Id
;
72 Typ
: Entity_Id
) return Boolean;
73 -- A static array aggregate in an object declaration can in most cases be
74 -- expanded in place. The one exception is when the aggregate is given
75 -- with component associations that specify different bounds from those of
76 -- the type definition in the object declaration. In this pathological
77 -- case the aggregate must slide, and we must introduce an intermediate
78 -- temporary to hold it.
80 -- The same holds in an assignment to one-dimensional array of arrays,
81 -- when a component may be given with bounds that differ from those of the
84 procedure Sort_Case_Table
(Case_Table
: in out Case_Table_Type
);
85 -- Sort the Case Table using the Lower Bound of each Choice as the key.
86 -- A simple insertion sort is used since the number of choices in a case
87 -- statement of variant part will usually be small and probably in near
90 function Has_Default_Init_Comps
(N
: Node_Id
) return Boolean;
91 -- N is an aggregate (record or array). Checks the presence of default
92 -- initialization (<>) in any component (Ada 2005: AI-287)
94 ------------------------------------------------------
95 -- Local subprograms for Record Aggregate Expansion --
96 ------------------------------------------------------
98 procedure Expand_Record_Aggregate
100 Orig_Tag
: Node_Id
:= Empty
;
101 Parent_Expr
: Node_Id
:= Empty
);
102 -- This is the top level procedure for record aggregate expansion.
103 -- Expansion for record aggregates needs expand aggregates for tagged
104 -- record types. Specifically Expand_Record_Aggregate adds the Tag
105 -- field in front of the Component_Association list that was created
106 -- during resolution by Resolve_Record_Aggregate.
108 -- N is the record aggregate node.
109 -- Orig_Tag is the value of the Tag that has to be provided for this
110 -- specific aggregate. It carries the tag corresponding to the type
111 -- of the outermost aggregate during the recursive expansion
112 -- Parent_Expr is the ancestor part of the original extension
115 procedure Convert_To_Assignments
(N
: Node_Id
; Typ
: Entity_Id
);
116 -- N is an N_Aggregate of a N_Extension_Aggregate. Typ is the type of
117 -- the aggregate. Transform the given aggregate into a sequence of
118 -- assignments component per component.
120 function Build_Record_Aggr_Code
124 Flist
: Node_Id
:= Empty
;
125 Obj
: Entity_Id
:= Empty
;
126 Is_Limited_Ancestor_Expansion
: Boolean := False) return List_Id
;
127 -- N is an N_Aggregate or a N_Extension_Aggregate. Typ is the type of the
128 -- aggregate. Target is an expression containing the location on which the
129 -- component by component assignments will take place. Returns the list of
130 -- assignments plus all other adjustments needed for tagged and controlled
131 -- types. Flist is an expression representing the finalization list on
132 -- which to attach the controlled components if any. Obj is present in the
133 -- object declaration and dynamic allocation cases, it contains an entity
134 -- that allows to know if the value being created needs to be attached to
135 -- the final list in case of pragma finalize_Storage_Only.
137 -- Is_Limited_Ancestor_Expansion indicates that the function has been
138 -- called recursively to expand the limited ancestor to avoid copying it.
140 function Has_Mutable_Components
(Typ
: Entity_Id
) return Boolean;
141 -- Return true if one of the component is of a discriminated type with
142 -- defaults. An aggregate for a type with mutable components must be
143 -- expanded into individual assignments.
145 procedure Initialize_Discriminants
(N
: Node_Id
; Typ
: Entity_Id
);
146 -- If the type of the aggregate is a type extension with renamed discrimi-
147 -- nants, we must initialize the hidden discriminants of the parent.
148 -- Otherwise, the target object must not be initialized. The discriminants
149 -- are initialized by calling the initialization procedure for the type.
150 -- This is incorrect if the initialization of other components has any
151 -- side effects. We restrict this call to the case where the parent type
152 -- has a variant part, because this is the only case where the hidden
153 -- discriminants are accessed, namely when calling discriminant checking
154 -- functions of the parent type, and when applying a stream attribute to
155 -- an object of the derived type.
157 -----------------------------------------------------
158 -- Local Subprograms for Array Aggregate Expansion --
159 -----------------------------------------------------
161 procedure Convert_Array_Aggr_In_Allocator
165 -- If the aggregate appears within an allocator and can be expanded in
166 -- place, this routine generates the individual assignments to components
167 -- of the designated object. This is an optimization over the general
168 -- case, where a temporary is first created on the stack and then used to
169 -- construct the allocated object on the heap.
171 procedure Convert_To_Positional
173 Max_Others_Replicate
: Nat
:= 5;
174 Handle_Bit_Packed
: Boolean := False);
175 -- If possible, convert named notation to positional notation. This
176 -- conversion is possible only in some static cases. If the conversion is
177 -- possible, then N is rewritten with the analyzed converted aggregate.
178 -- The parameter Max_Others_Replicate controls the maximum number of
179 -- values corresponding to an others choice that will be converted to
180 -- positional notation (the default of 5 is the normal limit, and reflects
181 -- the fact that normally the loop is better than a lot of separate
182 -- assignments). Note that this limit gets overridden in any case if
183 -- either of the restrictions No_Elaboration_Code or No_Implicit_Loops is
184 -- set. The parameter Handle_Bit_Packed is usually set False (since we do
185 -- not expect the back end to handle bit packed arrays, so the normal case
186 -- of conversion is pointless), but in the special case of a call from
187 -- Packed_Array_Aggregate_Handled, we set this parameter to True, since
188 -- these are cases we handle in there.
190 procedure Expand_Array_Aggregate
(N
: Node_Id
);
191 -- This is the top-level routine to perform array aggregate expansion.
192 -- N is the N_Aggregate node to be expanded.
194 function Backend_Processing_Possible
(N
: Node_Id
) return Boolean;
195 -- This function checks if array aggregate N can be processed directly
196 -- by Gigi. If this is the case True is returned.
198 function Build_Array_Aggr_Code
203 Scalar_Comp
: Boolean;
204 Indices
: List_Id
:= No_List
;
205 Flist
: Node_Id
:= Empty
) return List_Id
;
206 -- This recursive routine returns a list of statements containing the
207 -- loops and assignments that are needed for the expansion of the array
210 -- N is the (sub-)aggregate node to be expanded into code. This node
211 -- has been fully analyzed, and its Etype is properly set.
213 -- Index is the index node corresponding to the array sub-aggregate N.
215 -- Into is the target expression into which we are copying the aggregate.
216 -- Note that this node may not have been analyzed yet, and so the Etype
217 -- field may not be set.
219 -- Scalar_Comp is True if the component type of the aggregate is scalar.
221 -- Indices is the current list of expressions used to index the
222 -- object we are writing into.
224 -- Flist is an expression representing the finalization list on which
225 -- to attach the controlled components if any.
227 function Number_Of_Choices
(N
: Node_Id
) return Nat
;
228 -- Returns the number of discrete choices (not including the others choice
229 -- if present) contained in (sub-)aggregate N.
231 function Late_Expansion
235 Flist
: Node_Id
:= Empty
;
236 Obj
: Entity_Id
:= Empty
) return List_Id
;
237 -- N is a nested (record or array) aggregate that has been marked with
238 -- 'Delay_Expansion'. Typ is the expected type of the aggregate and Target
239 -- is a (duplicable) expression that will hold the result of the aggregate
240 -- expansion. Flist is the finalization list to be used to attach
241 -- controlled components. 'Obj' when non empty, carries the original
242 -- object being initialized in order to know if it needs to be attached to
243 -- the previous parameter which may not be the case in the case where
244 -- Finalize_Storage_Only is set. Basically this procedure is used to
245 -- implement top-down expansions of nested aggregates. This is necessary
246 -- for avoiding temporaries at each level as well as for propagating the
247 -- right internal finalization list.
249 function Make_OK_Assignment_Statement
252 Expression
: Node_Id
) return Node_Id
;
253 -- This is like Make_Assignment_Statement, except that Assignment_OK
254 -- is set in the left operand. All assignments built by this unit
255 -- use this routine. This is needed to deal with assignments to
256 -- initialized constants that are done in place.
258 function Packed_Array_Aggregate_Handled
(N
: Node_Id
) return Boolean;
259 -- Given an array aggregate, this function handles the case of a packed
260 -- array aggregate with all constant values, where the aggregate can be
261 -- evaluated at compile time. If this is possible, then N is rewritten
262 -- to be its proper compile time value with all the components properly
263 -- assembled. The expression is analyzed and resolved and True is
264 -- returned. If this transformation is not possible, N is unchanged
265 -- and False is returned
267 function Safe_Slice_Assignment
(N
: Node_Id
) return Boolean;
268 -- If a slice assignment has an aggregate with a single others_choice,
269 -- the assignment can be done in place even if bounds are not static,
270 -- by converting it into a loop over the discrete range of the slice.
272 ---------------------------------
273 -- Backend_Processing_Possible --
274 ---------------------------------
276 -- Backend processing by Gigi/gcc is possible only if all the following
277 -- conditions are met:
279 -- 1. N is fully positional
281 -- 2. N is not a bit-packed array aggregate;
283 -- 3. The size of N's array type must be known at compile time. Note
284 -- that this implies that the component size is also known
286 -- 4. The array type of N does not follow the Fortran layout convention
287 -- or if it does it must be 1 dimensional.
289 -- 5. The array component type is tagged, which may necessitate
290 -- reassignment of proper tags.
292 -- 6. The array component type might have unaligned bit components
294 function Backend_Processing_Possible
(N
: Node_Id
) return Boolean is
295 Typ
: constant Entity_Id
:= Etype
(N
);
296 -- Typ is the correct constrained array subtype of the aggregate
298 function Static_Check
(N
: Node_Id
; Index
: Node_Id
) return Boolean;
299 -- Recursively checks that N is fully positional, returns true if so
305 function Static_Check
(N
: Node_Id
; Index
: Node_Id
) return Boolean is
309 -- Check for component associations
311 if Present
(Component_Associations
(N
)) then
315 -- Recurse to check subaggregates, which may appear in qualified
316 -- expressions. If delayed, the front-end will have to expand.
318 Expr
:= First
(Expressions
(N
));
320 while Present
(Expr
) loop
322 if Is_Delayed_Aggregate
(Expr
) then
326 if Present
(Next_Index
(Index
))
327 and then not Static_Check
(Expr
, Next_Index
(Index
))
338 -- Start of processing for Backend_Processing_Possible
341 -- Checks 2 (array must not be bit packed)
343 if Is_Bit_Packed_Array
(Typ
) then
347 -- Checks 4 (array must not be multi-dimensional Fortran case)
349 if Convention
(Typ
) = Convention_Fortran
350 and then Number_Dimensions
(Typ
) > 1
355 -- Checks 3 (size of array must be known at compile time)
357 if not Size_Known_At_Compile_Time
(Typ
) then
361 -- Checks 1 (aggregate must be fully positional)
363 if not Static_Check
(N
, First_Index
(Typ
)) then
367 -- Checks 5 (if the component type is tagged, then we may need
368 -- to do tag adjustments; perhaps this should be refined to check for
369 -- any component associations that actually need tag adjustment,
370 -- along the lines of the test that is carried out in
371 -- Has_Delayed_Nested_Aggregate_Or_Tagged_Comps for record aggregates
372 -- with tagged components, but not clear whether it's worthwhile ???;
373 -- in the case of the JVM, object tags are handled implicitly)
375 if Is_Tagged_Type
(Component_Type
(Typ
)) and then not Java_VM
then
379 -- Checks 6 (component type must not have bit aligned components)
381 if Type_May_Have_Bit_Aligned_Components
(Component_Type
(Typ
)) then
385 -- Backend processing is possible
387 Set_Compile_Time_Known_Aggregate
(N
, True);
388 Set_Size_Known_At_Compile_Time
(Etype
(N
), True);
390 end Backend_Processing_Possible
;
392 ---------------------------
393 -- Build_Array_Aggr_Code --
394 ---------------------------
396 -- The code that we generate from a one dimensional aggregate is
398 -- 1. If the sub-aggregate contains discrete choices we
400 -- (a) Sort the discrete choices
402 -- (b) Otherwise for each discrete choice that specifies a range we
403 -- emit a loop. If a range specifies a maximum of three values, or
404 -- we are dealing with an expression we emit a sequence of
405 -- assignments instead of a loop.
407 -- (c) Generate the remaining loops to cover the others choice if any
409 -- 2. If the aggregate contains positional elements we
411 -- (a) translate the positional elements in a series of assignments
413 -- (b) Generate a final loop to cover the others choice if any.
414 -- Note that this final loop has to be a while loop since the case
416 -- L : Integer := Integer'Last;
417 -- H : Integer := Integer'Last;
418 -- A : array (L .. H) := (1, others =>0);
420 -- cannot be handled by a for loop. Thus for the following
422 -- array (L .. H) := (.. positional elements.., others =>E);
424 -- we always generate something like:
426 -- J : Index_Type := Index_Of_Last_Positional_Element;
428 -- J := Index_Base'Succ (J)
432 function Build_Array_Aggr_Code
437 Scalar_Comp
: Boolean;
438 Indices
: List_Id
:= No_List
;
439 Flist
: Node_Id
:= Empty
) return List_Id
441 Loc
: constant Source_Ptr
:= Sloc
(N
);
442 Index_Base
: constant Entity_Id
:= Base_Type
(Etype
(Index
));
443 Index_Base_L
: constant Node_Id
:= Type_Low_Bound
(Index_Base
);
444 Index_Base_H
: constant Node_Id
:= Type_High_Bound
(Index_Base
);
446 function Add
(Val
: Int
; To
: Node_Id
) return Node_Id
;
447 -- Returns an expression where Val is added to expression To, unless
448 -- To+Val is provably out of To's base type range. To must be an
449 -- already analyzed expression.
451 function Empty_Range
(L
, H
: Node_Id
) return Boolean;
452 -- Returns True if the range defined by L .. H is certainly empty
454 function Equal
(L
, H
: Node_Id
) return Boolean;
455 -- Returns True if L = H for sure
457 function Index_Base_Name
return Node_Id
;
458 -- Returns a new reference to the index type name
460 function Gen_Assign
(Ind
: Node_Id
; Expr
: Node_Id
) return List_Id
;
461 -- Ind must be a side-effect free expression. If the input aggregate
462 -- N to Build_Loop contains no sub-aggregates, then this function
463 -- returns the assignment statement:
465 -- Into (Indices, Ind) := Expr;
467 -- Otherwise we call Build_Code recursively
469 -- Ada 2005 (AI-287): In case of default initialized component, Expr
470 -- is empty and we generate a call to the corresponding IP subprogram.
472 function Gen_Loop
(L
, H
: Node_Id
; Expr
: Node_Id
) return List_Id
;
473 -- Nodes L and H must be side-effect free expressions.
474 -- If the input aggregate N to Build_Loop contains no sub-aggregates,
475 -- This routine returns the for loop statement
477 -- for J in Index_Base'(L) .. Index_Base'(H) loop
478 -- Into (Indices, J) := Expr;
481 -- Otherwise we call Build_Code recursively.
482 -- As an optimization if the loop covers 3 or less scalar elements we
483 -- generate a sequence of assignments.
485 function Gen_While
(L
, H
: Node_Id
; Expr
: Node_Id
) return List_Id
;
486 -- Nodes L and H must be side-effect free expressions.
487 -- If the input aggregate N to Build_Loop contains no sub-aggregates,
488 -- This routine returns the while loop statement
490 -- J : Index_Base := L;
492 -- J := Index_Base'Succ (J);
493 -- Into (Indices, J) := Expr;
496 -- Otherwise we call Build_Code recursively
498 function Local_Compile_Time_Known_Value
(E
: Node_Id
) return Boolean;
499 function Local_Expr_Value
(E
: Node_Id
) return Uint
;
500 -- These two Local routines are used to replace the corresponding ones
501 -- in sem_eval because while processing the bounds of an aggregate with
502 -- discrete choices whose index type is an enumeration, we build static
503 -- expressions not recognized by Compile_Time_Known_Value as such since
504 -- they have not yet been analyzed and resolved. All the expressions in
505 -- question are things like Index_Base_Name'Val (Const) which we can
506 -- easily recognize as being constant.
512 function Add
(Val
: Int
; To
: Node_Id
) return Node_Id
is
517 U_Val
: constant Uint
:= UI_From_Int
(Val
);
520 -- Note: do not try to optimize the case of Val = 0, because
521 -- we need to build a new node with the proper Sloc value anyway.
523 -- First test if we can do constant folding
525 if Local_Compile_Time_Known_Value
(To
) then
526 U_To
:= Local_Expr_Value
(To
) + Val
;
528 -- Determine if our constant is outside the range of the index.
529 -- If so return an Empty node. This empty node will be caught
530 -- by Empty_Range below.
532 if Compile_Time_Known_Value
(Index_Base_L
)
533 and then U_To
< Expr_Value
(Index_Base_L
)
537 elsif Compile_Time_Known_Value
(Index_Base_H
)
538 and then U_To
> Expr_Value
(Index_Base_H
)
543 Expr_Pos
:= Make_Integer_Literal
(Loc
, U_To
);
544 Set_Is_Static_Expression
(Expr_Pos
);
546 if not Is_Enumeration_Type
(Index_Base
) then
549 -- If we are dealing with enumeration return
550 -- Index_Base'Val (Expr_Pos)
554 Make_Attribute_Reference
556 Prefix
=> Index_Base_Name
,
557 Attribute_Name
=> Name_Val
,
558 Expressions
=> New_List
(Expr_Pos
));
564 -- If we are here no constant folding possible
566 if not Is_Enumeration_Type
(Index_Base
) then
569 Left_Opnd
=> Duplicate_Subexpr
(To
),
570 Right_Opnd
=> Make_Integer_Literal
(Loc
, U_Val
));
572 -- If we are dealing with enumeration return
573 -- Index_Base'Val (Index_Base'Pos (To) + Val)
577 Make_Attribute_Reference
579 Prefix
=> Index_Base_Name
,
580 Attribute_Name
=> Name_Pos
,
581 Expressions
=> New_List
(Duplicate_Subexpr
(To
)));
586 Right_Opnd
=> Make_Integer_Literal
(Loc
, U_Val
));
589 Make_Attribute_Reference
591 Prefix
=> Index_Base_Name
,
592 Attribute_Name
=> Name_Val
,
593 Expressions
=> New_List
(Expr_Pos
));
603 function Empty_Range
(L
, H
: Node_Id
) return Boolean is
604 Is_Empty
: Boolean := False;
609 -- First check if L or H were already detected as overflowing the
610 -- index base range type by function Add above. If this is so Add
611 -- returns the empty node.
613 if No
(L
) or else No
(H
) then
620 -- L > H range is empty
626 -- B_L > H range must be empty
632 -- L > B_H range must be empty
636 High
:= Index_Base_H
;
639 if Local_Compile_Time_Known_Value
(Low
)
640 and then Local_Compile_Time_Known_Value
(High
)
643 UI_Gt
(Local_Expr_Value
(Low
), Local_Expr_Value
(High
));
656 function Equal
(L
, H
: Node_Id
) return Boolean is
661 elsif Local_Compile_Time_Known_Value
(L
)
662 and then Local_Compile_Time_Known_Value
(H
)
664 return UI_Eq
(Local_Expr_Value
(L
), Local_Expr_Value
(H
));
674 function Gen_Assign
(Ind
: Node_Id
; Expr
: Node_Id
) return List_Id
is
675 L
: constant List_Id
:= New_List
;
679 New_Indices
: List_Id
;
680 Indexed_Comp
: Node_Id
;
682 Comp_Type
: Entity_Id
:= Empty
;
684 function Add_Loop_Actions
(Lis
: List_Id
) return List_Id
;
685 -- Collect insert_actions generated in the construction of a
686 -- loop, and prepend them to the sequence of assignments to
687 -- complete the eventual body of the loop.
689 ----------------------
690 -- Add_Loop_Actions --
691 ----------------------
693 function Add_Loop_Actions
(Lis
: List_Id
) return List_Id
is
697 -- Ada 2005 (AI-287): Do nothing else in case of default
698 -- initialized component.
700 if not Present
(Expr
) then
703 elsif Nkind
(Parent
(Expr
)) = N_Component_Association
704 and then Present
(Loop_Actions
(Parent
(Expr
)))
706 Append_List
(Lis
, Loop_Actions
(Parent
(Expr
)));
707 Res
:= Loop_Actions
(Parent
(Expr
));
708 Set_Loop_Actions
(Parent
(Expr
), No_List
);
714 end Add_Loop_Actions
;
716 -- Start of processing for Gen_Assign
720 New_Indices
:= New_List
;
722 New_Indices
:= New_Copy_List_Tree
(Indices
);
725 Append_To
(New_Indices
, Ind
);
727 if Present
(Flist
) then
728 F
:= New_Copy_Tree
(Flist
);
730 elsif Present
(Etype
(N
)) and then Controlled_Type
(Etype
(N
)) then
731 if Is_Entity_Name
(Into
)
732 and then Present
(Scope
(Entity
(Into
)))
734 F
:= Find_Final_List
(Scope
(Entity
(Into
)));
736 F
:= Find_Final_List
(Current_Scope
);
742 if Present
(Next_Index
(Index
)) then
745 Build_Array_Aggr_Code
748 Index
=> Next_Index
(Index
),
750 Scalar_Comp
=> Scalar_Comp
,
751 Indices
=> New_Indices
,
755 -- If we get here then we are at a bottom-level (sub-)aggregate
759 (Make_Indexed_Component
(Loc
,
760 Prefix
=> New_Copy_Tree
(Into
),
761 Expressions
=> New_Indices
));
763 Set_Assignment_OK
(Indexed_Comp
);
765 -- Ada 2005 (AI-287): In case of default initialized component, Expr
766 -- is not present (and therefore we also initialize Expr_Q to empty).
768 if not Present
(Expr
) then
770 elsif Nkind
(Expr
) = N_Qualified_Expression
then
771 Expr_Q
:= Expression
(Expr
);
776 if Present
(Etype
(N
))
777 and then Etype
(N
) /= Any_Composite
779 Comp_Type
:= Component_Type
(Etype
(N
));
780 pragma Assert
(Comp_Type
= Ctype
); -- AI-287
782 elsif Present
(Next
(First
(New_Indices
))) then
784 -- Ada 2005 (AI-287): Do nothing in case of default initialized
785 -- component because we have received the component type in
786 -- the formal parameter Ctype.
788 -- ??? Some assert pragmas have been added to check if this new
789 -- formal can be used to replace this code in all cases.
791 if Present
(Expr
) then
793 -- This is a multidimensional array. Recover the component
794 -- type from the outermost aggregate, because subaggregates
795 -- do not have an assigned type.
798 P
: Node_Id
:= Parent
(Expr
);
801 while Present
(P
) loop
802 if Nkind
(P
) = N_Aggregate
803 and then Present
(Etype
(P
))
805 Comp_Type
:= Component_Type
(Etype
(P
));
813 pragma Assert
(Comp_Type
= Ctype
); -- AI-287
818 -- Ada 2005 (AI-287): We only analyze the expression in case of non-
819 -- default initialized components (otherwise Expr_Q is not present).
822 and then (Nkind
(Expr_Q
) = N_Aggregate
823 or else Nkind
(Expr_Q
) = N_Extension_Aggregate
)
825 -- At this stage the Expression may not have been
826 -- analyzed yet because the array aggregate code has not
827 -- been updated to use the Expansion_Delayed flag and
828 -- avoid analysis altogether to solve the same problem
829 -- (see Resolve_Aggr_Expr). So let us do the analysis of
830 -- non-array aggregates now in order to get the value of
831 -- Expansion_Delayed flag for the inner aggregate ???
833 if Present
(Comp_Type
) and then not Is_Array_Type
(Comp_Type
) then
834 Analyze_And_Resolve
(Expr_Q
, Comp_Type
);
837 if Is_Delayed_Aggregate
(Expr_Q
) then
839 -- This is either a subaggregate of a multidimentional array,
840 -- or a component of an array type whose component type is
841 -- also an array. In the latter case, the expression may have
842 -- component associations that provide different bounds from
843 -- those of the component type, and sliding must occur. Instead
844 -- of decomposing the current aggregate assignment, force the
845 -- re-analysis of the assignment, so that a temporary will be
846 -- generated in the usual fashion, and sliding will take place.
848 if Nkind
(Parent
(N
)) = N_Assignment_Statement
849 and then Is_Array_Type
(Comp_Type
)
850 and then Present
(Component_Associations
(Expr_Q
))
851 and then Must_Slide
(Comp_Type
, Etype
(Expr_Q
))
853 Set_Expansion_Delayed
(Expr_Q
, False);
854 Set_Analyzed
(Expr_Q
, False);
860 Expr_Q
, Etype
(Expr_Q
), Indexed_Comp
, F
));
865 -- Ada 2005 (AI-287): In case of default initialized component, call
866 -- the initialization subprogram associated with the component type.
868 if not Present
(Expr
) then
870 if Present
(Base_Init_Proc
(Etype
(Ctype
)))
871 or else Has_Task
(Base_Type
(Ctype
))
874 Build_Initialization_Call
(Loc
,
875 Id_Ref
=> Indexed_Comp
,
877 With_Default_Init
=> True));
881 -- Now generate the assignment with no associated controlled
882 -- actions since the target of the assignment may not have
883 -- been initialized, it is not possible to Finalize it as
884 -- expected by normal controlled assignment. The rest of the
885 -- controlled actions are done manually with the proper
886 -- finalization list coming from the context.
889 Make_OK_Assignment_Statement
(Loc
,
890 Name
=> Indexed_Comp
,
891 Expression
=> New_Copy_Tree
(Expr
));
893 if Present
(Comp_Type
) and then Controlled_Type
(Comp_Type
) then
894 Set_No_Ctrl_Actions
(A
);
899 -- Adjust the tag if tagged (because of possible view
900 -- conversions), unless compiling for the Java VM
901 -- where tags are implicit.
903 if Present
(Comp_Type
)
904 and then Is_Tagged_Type
(Comp_Type
)
908 Make_OK_Assignment_Statement
(Loc
,
910 Make_Selected_Component
(Loc
,
911 Prefix
=> New_Copy_Tree
(Indexed_Comp
),
913 New_Reference_To
(Tag_Component
(Comp_Type
), Loc
)),
916 Unchecked_Convert_To
(RTE
(RE_Tag
),
918 Access_Disp_Table
(Comp_Type
), Loc
)));
923 -- Adjust and Attach the component to the proper final list
924 -- which can be the controller of the outer record object or
925 -- the final list associated with the scope
927 if Present
(Comp_Type
) and then Controlled_Type
(Comp_Type
) then
930 Ref
=> New_Copy_Tree
(Indexed_Comp
),
933 With_Attach
=> Make_Integer_Literal
(Loc
, 1)));
937 return Add_Loop_Actions
(L
);
944 function Gen_Loop
(L
, H
: Node_Id
; Expr
: Node_Id
) return List_Id
is
948 -- Index_Base'(L) .. Index_Base'(H)
950 L_Iteration_Scheme
: Node_Id
;
951 -- L_J in Index_Base'(L) .. Index_Base'(H)
954 -- The statements to execute in the loop
956 S
: constant List_Id
:= New_List
;
957 -- List of statements
960 -- Copy of expression tree, used for checking purposes
963 -- If loop bounds define an empty range return the null statement
965 if Empty_Range
(L
, H
) then
966 Append_To
(S
, Make_Null_Statement
(Loc
));
968 -- Ada 2005 (AI-287): Nothing else need to be done in case of
969 -- default initialized component.
971 if not Present
(Expr
) then
975 -- The expression must be type-checked even though no component
976 -- of the aggregate will have this value. This is done only for
977 -- actual components of the array, not for subaggregates. Do
978 -- the check on a copy, because the expression may be shared
979 -- among several choices, some of which might be non-null.
981 if Present
(Etype
(N
))
982 and then Is_Array_Type
(Etype
(N
))
983 and then No
(Next_Index
(Index
))
985 Expander_Mode_Save_And_Set
(False);
986 Tcopy
:= New_Copy_Tree
(Expr
);
987 Set_Parent
(Tcopy
, N
);
988 Analyze_And_Resolve
(Tcopy
, Component_Type
(Etype
(N
)));
989 Expander_Mode_Restore
;
995 -- If loop bounds are the same then generate an assignment
997 elsif Equal
(L
, H
) then
998 return Gen_Assign
(New_Copy_Tree
(L
), Expr
);
1000 -- If H - L <= 2 then generate a sequence of assignments
1001 -- when we are processing the bottom most aggregate and it contains
1002 -- scalar components.
1004 elsif No
(Next_Index
(Index
))
1005 and then Scalar_Comp
1006 and then Local_Compile_Time_Known_Value
(L
)
1007 and then Local_Compile_Time_Known_Value
(H
)
1008 and then Local_Expr_Value
(H
) - Local_Expr_Value
(L
) <= 2
1011 Append_List_To
(S
, Gen_Assign
(New_Copy_Tree
(L
), Expr
));
1012 Append_List_To
(S
, Gen_Assign
(Add
(1, To
=> L
), Expr
));
1014 if Local_Expr_Value
(H
) - Local_Expr_Value
(L
) = 2 then
1015 Append_List_To
(S
, Gen_Assign
(Add
(2, To
=> L
), Expr
));
1021 -- Otherwise construct the loop, starting with the loop index L_J
1023 L_J
:= Make_Defining_Identifier
(Loc
, New_Internal_Name
('J'));
1025 -- Construct "L .. H"
1030 Low_Bound
=> Make_Qualified_Expression
1032 Subtype_Mark
=> Index_Base_Name
,
1034 High_Bound
=> Make_Qualified_Expression
1036 Subtype_Mark
=> Index_Base_Name
,
1039 -- Construct "for L_J in Index_Base range L .. H"
1041 L_Iteration_Scheme
:=
1042 Make_Iteration_Scheme
1044 Loop_Parameter_Specification
=>
1045 Make_Loop_Parameter_Specification
1047 Defining_Identifier
=> L_J
,
1048 Discrete_Subtype_Definition
=> L_Range
));
1050 -- Construct the statements to execute in the loop body
1052 L_Body
:= Gen_Assign
(New_Reference_To
(L_J
, Loc
), Expr
);
1054 -- Construct the final loop
1056 Append_To
(S
, Make_Implicit_Loop_Statement
1058 Identifier
=> Empty
,
1059 Iteration_Scheme
=> L_Iteration_Scheme
,
1060 Statements
=> L_Body
));
1069 -- The code built is
1071 -- W_J : Index_Base := L;
1072 -- while W_J < H loop
1073 -- W_J := Index_Base'Succ (W);
1077 function Gen_While
(L
, H
: Node_Id
; Expr
: Node_Id
) return List_Id
is
1081 -- W_J : Base_Type := L;
1083 W_Iteration_Scheme
: Node_Id
;
1086 W_Index_Succ
: Node_Id
;
1087 -- Index_Base'Succ (J)
1089 W_Increment
: Node_Id
;
1090 -- W_J := Index_Base'Succ (W)
1092 W_Body
: constant List_Id
:= New_List
;
1093 -- The statements to execute in the loop
1095 S
: constant List_Id
:= New_List
;
1096 -- list of statement
1099 -- If loop bounds define an empty range or are equal return null
1101 if Empty_Range
(L
, H
) or else Equal
(L
, H
) then
1102 Append_To
(S
, Make_Null_Statement
(Loc
));
1106 -- Build the decl of W_J
1108 W_J
:= Make_Defining_Identifier
(Loc
, New_Internal_Name
('J'));
1110 Make_Object_Declaration
1112 Defining_Identifier
=> W_J
,
1113 Object_Definition
=> Index_Base_Name
,
1116 -- Theoretically we should do a New_Copy_Tree (L) here, but we know
1117 -- that in this particular case L is a fresh Expr generated by
1118 -- Add which we are the only ones to use.
1120 Append_To
(S
, W_Decl
);
1122 -- Construct " while W_J < H"
1124 W_Iteration_Scheme
:=
1125 Make_Iteration_Scheme
1127 Condition
=> Make_Op_Lt
1129 Left_Opnd
=> New_Reference_To
(W_J
, Loc
),
1130 Right_Opnd
=> New_Copy_Tree
(H
)));
1132 -- Construct the statements to execute in the loop body
1135 Make_Attribute_Reference
1137 Prefix
=> Index_Base_Name
,
1138 Attribute_Name
=> Name_Succ
,
1139 Expressions
=> New_List
(New_Reference_To
(W_J
, Loc
)));
1142 Make_OK_Assignment_Statement
1144 Name
=> New_Reference_To
(W_J
, Loc
),
1145 Expression
=> W_Index_Succ
);
1147 Append_To
(W_Body
, W_Increment
);
1148 Append_List_To
(W_Body
,
1149 Gen_Assign
(New_Reference_To
(W_J
, Loc
), Expr
));
1151 -- Construct the final loop
1153 Append_To
(S
, Make_Implicit_Loop_Statement
1155 Identifier
=> Empty
,
1156 Iteration_Scheme
=> W_Iteration_Scheme
,
1157 Statements
=> W_Body
));
1162 ---------------------
1163 -- Index_Base_Name --
1164 ---------------------
1166 function Index_Base_Name
return Node_Id
is
1168 return New_Reference_To
(Index_Base
, Sloc
(N
));
1169 end Index_Base_Name
;
1171 ------------------------------------
1172 -- Local_Compile_Time_Known_Value --
1173 ------------------------------------
1175 function Local_Compile_Time_Known_Value
(E
: Node_Id
) return Boolean is
1177 return Compile_Time_Known_Value
(E
)
1179 (Nkind
(E
) = N_Attribute_Reference
1180 and then Attribute_Name
(E
) = Name_Val
1181 and then Compile_Time_Known_Value
(First
(Expressions
(E
))));
1182 end Local_Compile_Time_Known_Value
;
1184 ----------------------
1185 -- Local_Expr_Value --
1186 ----------------------
1188 function Local_Expr_Value
(E
: Node_Id
) return Uint
is
1190 if Compile_Time_Known_Value
(E
) then
1191 return Expr_Value
(E
);
1193 return Expr_Value
(First
(Expressions
(E
)));
1195 end Local_Expr_Value
;
1197 -- Build_Array_Aggr_Code Variables
1204 Others_Expr
: Node_Id
:= Empty
;
1205 Others_Mbox_Present
: Boolean := False;
1207 Aggr_L
: constant Node_Id
:= Low_Bound
(Aggregate_Bounds
(N
));
1208 Aggr_H
: constant Node_Id
:= High_Bound
(Aggregate_Bounds
(N
));
1209 -- The aggregate bounds of this specific sub-aggregate. Note that if
1210 -- the code generated by Build_Array_Aggr_Code is executed then these
1211 -- bounds are OK. Otherwise a Constraint_Error would have been raised.
1213 Aggr_Low
: constant Node_Id
:= Duplicate_Subexpr_No_Checks
(Aggr_L
);
1214 Aggr_High
: constant Node_Id
:= Duplicate_Subexpr_No_Checks
(Aggr_H
);
1215 -- After Duplicate_Subexpr these are side-effect free
1220 Nb_Choices
: Nat
:= 0;
1221 Table
: Case_Table_Type
(1 .. Number_Of_Choices
(N
));
1222 -- Used to sort all the different choice values
1225 -- Number of elements in the positional aggregate
1227 New_Code
: constant List_Id
:= New_List
;
1229 -- Start of processing for Build_Array_Aggr_Code
1232 -- First before we start, a special case. if we have a bit packed
1233 -- array represented as a modular type, then clear the value to
1234 -- zero first, to ensure that unused bits are properly cleared.
1239 and then Is_Bit_Packed_Array
(Typ
)
1240 and then Is_Modular_Integer_Type
(Packed_Array_Type
(Typ
))
1242 Append_To
(New_Code
,
1243 Make_Assignment_Statement
(Loc
,
1244 Name
=> New_Copy_Tree
(Into
),
1246 Unchecked_Convert_To
(Typ
,
1247 Make_Integer_Literal
(Loc
, Uint_0
))));
1251 -- STEP 1: Process component associations
1252 -- For those associations that may generate a loop, initialize
1253 -- Loop_Actions to collect inserted actions that may be crated.
1255 if No
(Expressions
(N
)) then
1257 -- STEP 1 (a): Sort the discrete choices
1259 Assoc
:= First
(Component_Associations
(N
));
1260 while Present
(Assoc
) loop
1261 Choice
:= First
(Choices
(Assoc
));
1262 while Present
(Choice
) loop
1263 if Nkind
(Choice
) = N_Others_Choice
then
1264 Set_Loop_Actions
(Assoc
, New_List
);
1266 if Box_Present
(Assoc
) then
1267 Others_Mbox_Present
:= True;
1269 Others_Expr
:= Expression
(Assoc
);
1274 Get_Index_Bounds
(Choice
, Low
, High
);
1277 Set_Loop_Actions
(Assoc
, New_List
);
1280 Nb_Choices
:= Nb_Choices
+ 1;
1281 if Box_Present
(Assoc
) then
1282 Table
(Nb_Choices
) := (Choice_Lo
=> Low
,
1284 Choice_Node
=> Empty
);
1286 Table
(Nb_Choices
) := (Choice_Lo
=> Low
,
1288 Choice_Node
=> Expression
(Assoc
));
1296 -- If there is more than one set of choices these must be static
1297 -- and we can therefore sort them. Remember that Nb_Choices does not
1298 -- account for an others choice.
1300 if Nb_Choices
> 1 then
1301 Sort_Case_Table
(Table
);
1304 -- STEP 1 (b): take care of the whole set of discrete choices
1306 for J
in 1 .. Nb_Choices
loop
1307 Low
:= Table
(J
).Choice_Lo
;
1308 High
:= Table
(J
).Choice_Hi
;
1309 Expr
:= Table
(J
).Choice_Node
;
1310 Append_List
(Gen_Loop
(Low
, High
, Expr
), To
=> New_Code
);
1313 -- STEP 1 (c): generate the remaining loops to cover others choice
1314 -- We don't need to generate loops over empty gaps, but if there is
1315 -- a single empty range we must analyze the expression for semantics
1317 if Present
(Others_Expr
) or else Others_Mbox_Present
then
1319 First
: Boolean := True;
1322 for J
in 0 .. Nb_Choices
loop
1326 Low
:= Add
(1, To
=> Table
(J
).Choice_Hi
);
1329 if J
= Nb_Choices
then
1332 High
:= Add
(-1, To
=> Table
(J
+ 1).Choice_Lo
);
1335 -- If this is an expansion within an init proc, make
1336 -- sure that discriminant references are replaced by
1337 -- the corresponding discriminal.
1339 if Inside_Init_Proc
then
1340 if Is_Entity_Name
(Low
)
1341 and then Ekind
(Entity
(Low
)) = E_Discriminant
1343 Set_Entity
(Low
, Discriminal
(Entity
(Low
)));
1346 if Is_Entity_Name
(High
)
1347 and then Ekind
(Entity
(High
)) = E_Discriminant
1349 Set_Entity
(High
, Discriminal
(Entity
(High
)));
1354 or else not Empty_Range
(Low
, High
)
1358 (Gen_Loop
(Low
, High
, Others_Expr
), To
=> New_Code
);
1364 -- STEP 2: Process positional components
1367 -- STEP 2 (a): Generate the assignments for each positional element
1368 -- Note that here we have to use Aggr_L rather than Aggr_Low because
1369 -- Aggr_L is analyzed and Add wants an analyzed expression.
1371 Expr
:= First
(Expressions
(N
));
1374 while Present
(Expr
) loop
1375 Nb_Elements
:= Nb_Elements
+ 1;
1376 Append_List
(Gen_Assign
(Add
(Nb_Elements
, To
=> Aggr_L
), Expr
),
1381 -- STEP 2 (b): Generate final loop if an others choice is present
1382 -- Here Nb_Elements gives the offset of the last positional element.
1384 if Present
(Component_Associations
(N
)) then
1385 Assoc
:= Last
(Component_Associations
(N
));
1387 -- Ada 2005 (AI-287)
1389 if Box_Present
(Assoc
) then
1390 Append_List
(Gen_While
(Add
(Nb_Elements
, To
=> Aggr_L
),
1395 Expr
:= Expression
(Assoc
);
1397 Append_List
(Gen_While
(Add
(Nb_Elements
, To
=> Aggr_L
),
1406 end Build_Array_Aggr_Code
;
1408 ----------------------------
1409 -- Build_Record_Aggr_Code --
1410 ----------------------------
1412 function Build_Record_Aggr_Code
1416 Flist
: Node_Id
:= Empty
;
1417 Obj
: Entity_Id
:= Empty
;
1418 Is_Limited_Ancestor_Expansion
: Boolean := False) return List_Id
1420 Loc
: constant Source_Ptr
:= Sloc
(N
);
1421 L
: constant List_Id
:= New_List
;
1422 Start_L
: constant List_Id
:= New_List
;
1423 N_Typ
: constant Entity_Id
:= Etype
(N
);
1429 Comp_Type
: Entity_Id
;
1430 Selector
: Entity_Id
;
1431 Comp_Expr
: Node_Id
;
1434 Internal_Final_List
: Node_Id
;
1436 -- If this is an internal aggregate, the External_Final_List is an
1437 -- expression for the controller record of the enclosing type.
1438 -- If the current aggregate has several controlled components, this
1439 -- expression will appear in several calls to attach to the finali-
1440 -- zation list, and it must not be shared.
1442 External_Final_List
: Node_Id
;
1443 Ancestor_Is_Expression
: Boolean := False;
1444 Ancestor_Is_Subtype_Mark
: Boolean := False;
1446 Init_Typ
: Entity_Id
:= Empty
;
1449 function Get_Constraint_Association
(T
: Entity_Id
) return Node_Id
;
1450 -- Returns the first discriminant association in the constraint
1451 -- associated with T, if any, otherwise returns Empty.
1453 function Ancestor_Discriminant_Value
(Disc
: Entity_Id
) return Node_Id
;
1454 -- Returns the value that the given discriminant of an ancestor
1455 -- type should receive (in the absence of a conflict with the
1456 -- value provided by an ancestor part of an extension aggregate).
1458 procedure Check_Ancestor_Discriminants
(Anc_Typ
: Entity_Id
);
1459 -- Check that each of the discriminant values defined by the
1460 -- ancestor part of an extension aggregate match the corresponding
1461 -- values provided by either an association of the aggregate or
1462 -- by the constraint imposed by a parent type (RM95-4.3.2(8)).
1464 function Init_Controller
1469 Init_Pr
: Boolean) return List_Id
;
1470 -- returns the list of statements necessary to initialize the internal
1471 -- controller of the (possible) ancestor typ into target and attach
1472 -- it to finalization list F. Init_Pr conditions the call to the
1473 -- init proc since it may already be done due to ancestor initialization
1475 ---------------------------------
1476 -- Ancestor_Discriminant_Value --
1477 ---------------------------------
1479 function Ancestor_Discriminant_Value
(Disc
: Entity_Id
) return Node_Id
is
1481 Assoc_Elmt
: Elmt_Id
;
1482 Aggr_Comp
: Entity_Id
;
1483 Corresp_Disc
: Entity_Id
;
1484 Current_Typ
: Entity_Id
:= Base_Type
(Typ
);
1485 Parent_Typ
: Entity_Id
;
1486 Parent_Disc
: Entity_Id
;
1487 Save_Assoc
: Node_Id
:= Empty
;
1490 -- First check any discriminant associations to see if
1491 -- any of them provide a value for the discriminant.
1493 if Present
(Discriminant_Specifications
(Parent
(Current_Typ
))) then
1494 Assoc
:= First
(Component_Associations
(N
));
1495 while Present
(Assoc
) loop
1496 Aggr_Comp
:= Entity
(First
(Choices
(Assoc
)));
1498 if Ekind
(Aggr_Comp
) = E_Discriminant
then
1499 Save_Assoc
:= Expression
(Assoc
);
1501 Corresp_Disc
:= Corresponding_Discriminant
(Aggr_Comp
);
1502 while Present
(Corresp_Disc
) loop
1503 -- If found a corresponding discriminant then return
1504 -- the value given in the aggregate. (Note: this is
1505 -- not correct in the presence of side effects. ???)
1507 if Disc
= Corresp_Disc
then
1508 return Duplicate_Subexpr
(Expression
(Assoc
));
1512 Corresponding_Discriminant
(Corresp_Disc
);
1520 -- No match found in aggregate, so chain up parent types to find
1521 -- a constraint that defines the value of the discriminant.
1523 Parent_Typ
:= Etype
(Current_Typ
);
1524 while Current_Typ
/= Parent_Typ
loop
1525 if Has_Discriminants
(Parent_Typ
) then
1526 Parent_Disc
:= First_Discriminant
(Parent_Typ
);
1528 -- We either get the association from the subtype indication
1529 -- of the type definition itself, or from the discriminant
1530 -- constraint associated with the type entity (which is
1531 -- preferable, but it's not always present ???)
1533 if Is_Empty_Elmt_List
(
1534 Discriminant_Constraint
(Current_Typ
))
1536 Assoc
:= Get_Constraint_Association
(Current_Typ
);
1537 Assoc_Elmt
:= No_Elmt
;
1540 First_Elmt
(Discriminant_Constraint
(Current_Typ
));
1541 Assoc
:= Node
(Assoc_Elmt
);
1544 -- Traverse the discriminants of the parent type looking
1545 -- for one that corresponds.
1547 while Present
(Parent_Disc
) and then Present
(Assoc
) loop
1548 Corresp_Disc
:= Parent_Disc
;
1549 while Present
(Corresp_Disc
)
1550 and then Disc
/= Corresp_Disc
1553 Corresponding_Discriminant
(Corresp_Disc
);
1556 if Disc
= Corresp_Disc
then
1557 if Nkind
(Assoc
) = N_Discriminant_Association
then
1558 Assoc
:= Expression
(Assoc
);
1561 -- If the located association directly denotes
1562 -- a discriminant, then use the value of a saved
1563 -- association of the aggregate. This is a kludge
1564 -- to handle certain cases involving multiple
1565 -- discriminants mapped to a single discriminant
1566 -- of a descendant. It's not clear how to locate the
1567 -- appropriate discriminant value for such cases. ???
1569 if Is_Entity_Name
(Assoc
)
1570 and then Ekind
(Entity
(Assoc
)) = E_Discriminant
1572 Assoc
:= Save_Assoc
;
1575 return Duplicate_Subexpr
(Assoc
);
1578 Next_Discriminant
(Parent_Disc
);
1580 if No
(Assoc_Elmt
) then
1583 Next_Elmt
(Assoc_Elmt
);
1584 if Present
(Assoc_Elmt
) then
1585 Assoc
:= Node
(Assoc_Elmt
);
1593 Current_Typ
:= Parent_Typ
;
1594 Parent_Typ
:= Etype
(Current_Typ
);
1597 -- In some cases there's no ancestor value to locate (such as
1598 -- when an ancestor part given by an expression defines the
1599 -- discriminant value).
1602 end Ancestor_Discriminant_Value
;
1604 ----------------------------------
1605 -- Check_Ancestor_Discriminants --
1606 ----------------------------------
1608 procedure Check_Ancestor_Discriminants
(Anc_Typ
: Entity_Id
) is
1609 Discr
: Entity_Id
:= First_Discriminant
(Base_Type
(Anc_Typ
));
1610 Disc_Value
: Node_Id
;
1614 while Present
(Discr
) loop
1615 Disc_Value
:= Ancestor_Discriminant_Value
(Discr
);
1617 if Present
(Disc_Value
) then
1618 Cond
:= Make_Op_Ne
(Loc
,
1620 Make_Selected_Component
(Loc
,
1621 Prefix
=> New_Copy_Tree
(Target
),
1622 Selector_Name
=> New_Occurrence_Of
(Discr
, Loc
)),
1623 Right_Opnd
=> Disc_Value
);
1626 Make_Raise_Constraint_Error
(Loc
,
1628 Reason
=> CE_Discriminant_Check_Failed
));
1631 Next_Discriminant
(Discr
);
1633 end Check_Ancestor_Discriminants
;
1635 --------------------------------
1636 -- Get_Constraint_Association --
1637 --------------------------------
1639 function Get_Constraint_Association
(T
: Entity_Id
) return Node_Id
is
1640 Typ_Def
: constant Node_Id
:= Type_Definition
(Parent
(T
));
1641 Indic
: constant Node_Id
:= Subtype_Indication
(Typ_Def
);
1644 -- ??? Also need to cover case of a type mark denoting a subtype
1647 if Nkind
(Indic
) = N_Subtype_Indication
1648 and then Present
(Constraint
(Indic
))
1650 return First
(Constraints
(Constraint
(Indic
)));
1654 end Get_Constraint_Association
;
1656 ---------------------
1657 -- Init_controller --
1658 ---------------------
1660 function Init_Controller
1665 Init_Pr
: Boolean) return List_Id
1667 L
: constant List_Id
:= New_List
;
1672 -- init-proc (target._controller);
1673 -- initialize (target._controller);
1674 -- Attach_to_Final_List (target._controller, F);
1677 Make_Selected_Component
(Loc
,
1678 Prefix
=> Convert_To
(Typ
, New_Copy_Tree
(Target
)),
1679 Selector_Name
=> Make_Identifier
(Loc
, Name_uController
));
1680 Set_Assignment_OK
(Ref
);
1682 -- Ada 2005 (AI-287): Give support to default initialization of
1683 -- limited types and components.
1685 if (Nkind
(Target
) = N_Identifier
1686 and then Present
(Etype
(Target
))
1687 and then Is_Limited_Type
(Etype
(Target
)))
1689 (Nkind
(Target
) = N_Selected_Component
1690 and then Present
(Etype
(Selector_Name
(Target
)))
1691 and then Is_Limited_Type
(Etype
(Selector_Name
(Target
))))
1693 (Nkind
(Target
) = N_Unchecked_Type_Conversion
1694 and then Present
(Etype
(Target
))
1695 and then Is_Limited_Type
(Etype
(Target
)))
1697 (Nkind
(Target
) = N_Unchecked_Expression
1698 and then Nkind
(Expression
(Target
)) = N_Indexed_Component
1699 and then Present
(Etype
(Prefix
(Expression
(Target
))))
1700 and then Is_Limited_Type
(Etype
(Prefix
(Expression
(Target
)))))
1704 Build_Initialization_Call
(Loc
,
1706 Typ
=> RTE
(RE_Limited_Record_Controller
),
1707 In_Init_Proc
=> Within_Init_Proc
));
1711 Make_Procedure_Call_Statement
(Loc
,
1714 (Find_Prim_Op
(RTE
(RE_Limited_Record_Controller
),
1715 Name_Initialize
), Loc
),
1716 Parameter_Associations
=> New_List
(New_Copy_Tree
(Ref
))));
1721 Build_Initialization_Call
(Loc
,
1723 Typ
=> RTE
(RE_Record_Controller
),
1724 In_Init_Proc
=> Within_Init_Proc
));
1728 Make_Procedure_Call_Statement
(Loc
,
1730 New_Reference_To
(Find_Prim_Op
(RTE
(RE_Record_Controller
),
1731 Name_Initialize
), Loc
),
1732 Parameter_Associations
=> New_List
(New_Copy_Tree
(Ref
))));
1738 Obj_Ref
=> New_Copy_Tree
(Ref
),
1740 With_Attach
=> Attach
));
1742 end Init_Controller
;
1744 -- Start of processing for Build_Record_Aggr_Code
1747 -- Deal with the ancestor part of extension aggregates
1748 -- or with the discriminants of the root type
1750 if Nkind
(N
) = N_Extension_Aggregate
then
1752 A
: constant Node_Id
:= Ancestor_Part
(N
);
1755 -- If the ancestor part is a subtype mark "T", we generate
1757 -- init-proc (T(tmp)); if T is constrained and
1758 -- init-proc (S(tmp)); where S applies an appropriate
1759 -- constraint if T is unconstrained
1761 if Is_Entity_Name
(A
) and then Is_Type
(Entity
(A
)) then
1762 Ancestor_Is_Subtype_Mark
:= True;
1764 if Is_Constrained
(Entity
(A
)) then
1765 Init_Typ
:= Entity
(A
);
1767 -- For an ancestor part given by an unconstrained type
1768 -- mark, create a subtype constrained by appropriate
1769 -- corresponding discriminant values coming from either
1770 -- associations of the aggregate or a constraint on
1771 -- a parent type. The subtype will be used to generate
1772 -- the correct default value for the ancestor part.
1774 elsif Has_Discriminants
(Entity
(A
)) then
1776 Anc_Typ
: constant Entity_Id
:= Entity
(A
);
1777 Anc_Constr
: constant List_Id
:= New_List
;
1778 Discrim
: Entity_Id
;
1779 Disc_Value
: Node_Id
;
1780 New_Indic
: Node_Id
;
1781 Subt_Decl
: Node_Id
;
1784 Discrim
:= First_Discriminant
(Anc_Typ
);
1785 while Present
(Discrim
) loop
1786 Disc_Value
:= Ancestor_Discriminant_Value
(Discrim
);
1787 Append_To
(Anc_Constr
, Disc_Value
);
1788 Next_Discriminant
(Discrim
);
1792 Make_Subtype_Indication
(Loc
,
1793 Subtype_Mark
=> New_Occurrence_Of
(Anc_Typ
, Loc
),
1795 Make_Index_Or_Discriminant_Constraint
(Loc
,
1796 Constraints
=> Anc_Constr
));
1798 Init_Typ
:= Create_Itype
(Ekind
(Anc_Typ
), N
);
1801 Make_Subtype_Declaration
(Loc
,
1802 Defining_Identifier
=> Init_Typ
,
1803 Subtype_Indication
=> New_Indic
);
1805 -- Itypes must be analyzed with checks off
1806 -- Declaration must have a parent for proper
1807 -- handling of subsidiary actions.
1809 Set_Parent
(Subt_Decl
, N
);
1810 Analyze
(Subt_Decl
, Suppress
=> All_Checks
);
1814 Ref
:= Convert_To
(Init_Typ
, New_Copy_Tree
(Target
));
1815 Set_Assignment_OK
(Ref
);
1817 if Has_Default_Init_Comps
(N
)
1818 or else Has_Task
(Base_Type
(Init_Typ
))
1820 Append_List_To
(Start_L
,
1821 Build_Initialization_Call
(Loc
,
1824 In_Init_Proc
=> Within_Init_Proc
,
1825 With_Default_Init
=> True));
1827 Append_List_To
(Start_L
,
1828 Build_Initialization_Call
(Loc
,
1831 In_Init_Proc
=> Within_Init_Proc
));
1834 if Is_Constrained
(Entity
(A
))
1835 and then Has_Discriminants
(Entity
(A
))
1837 Check_Ancestor_Discriminants
(Entity
(A
));
1840 -- Ada 2005 (AI-287): If the ancestor part is a limited type,
1841 -- a recursive call expands the ancestor.
1843 elsif Is_Limited_Type
(Etype
(A
)) then
1844 Ancestor_Is_Expression
:= True;
1846 Append_List_To
(Start_L
,
1847 Build_Record_Aggr_Code
(
1848 N
=> Expression
(A
),
1849 Typ
=> Etype
(Expression
(A
)),
1853 Is_Limited_Ancestor_Expansion
=> True));
1855 -- If the ancestor part is an expression "E", we generate
1859 Ancestor_Is_Expression
:= True;
1860 Init_Typ
:= Etype
(A
);
1862 -- Assign the tag before doing the assignment to make sure
1863 -- that the dispatching call in the subsequent deep_adjust
1864 -- works properly (unless Java_VM, where tags are implicit).
1868 Make_OK_Assignment_Statement
(Loc
,
1870 Make_Selected_Component
(Loc
,
1871 Prefix
=> New_Copy_Tree
(Target
),
1872 Selector_Name
=> New_Reference_To
(
1873 Tag_Component
(Base_Type
(Typ
)), Loc
)),
1876 Unchecked_Convert_To
(RTE
(RE_Tag
),
1878 Access_Disp_Table
(Base_Type
(Typ
)), Loc
)));
1880 Set_Assignment_OK
(Name
(Instr
));
1881 Append_To
(L
, Instr
);
1884 -- If the ancestor part is an aggregate, force its full
1885 -- expansion, which was delayed.
1887 if Nkind
(A
) = N_Qualified_Expression
1888 and then (Nkind
(Expression
(A
)) = N_Aggregate
1890 Nkind
(Expression
(A
)) = N_Extension_Aggregate
)
1892 Set_Analyzed
(A
, False);
1893 Set_Analyzed
(Expression
(A
), False);
1896 Ref
:= Convert_To
(Init_Typ
, New_Copy_Tree
(Target
));
1897 Set_Assignment_OK
(Ref
);
1899 Make_Unsuppress_Block
(Loc
,
1900 Name_Discriminant_Check
,
1902 Make_OK_Assignment_Statement
(Loc
,
1904 Expression
=> A
))));
1906 if Has_Discriminants
(Init_Typ
) then
1907 Check_Ancestor_Discriminants
(Init_Typ
);
1912 -- Normal case (not an extension aggregate)
1915 -- Generate the discriminant expressions, component by component.
1916 -- If the base type is an unchecked union, the discriminants are
1917 -- unknown to the back-end and absent from a value of the type, so
1918 -- assignments for them are not emitted.
1920 if Has_Discriminants
(Typ
)
1921 and then not Is_Unchecked_Union
(Base_Type
(Typ
))
1923 -- ??? The discriminants of the object not inherited in the type
1924 -- of the object should be initialized here
1928 -- Generate discriminant init values
1931 Discriminant
: Entity_Id
;
1932 Discriminant_Value
: Node_Id
;
1935 Discriminant
:= First_Stored_Discriminant
(Typ
);
1937 while Present
(Discriminant
) loop
1940 Make_Selected_Component
(Loc
,
1941 Prefix
=> New_Copy_Tree
(Target
),
1942 Selector_Name
=> New_Occurrence_Of
(Discriminant
, Loc
));
1944 Discriminant_Value
:=
1945 Get_Discriminant_Value
(
1948 Discriminant_Constraint
(N_Typ
));
1951 Make_OK_Assignment_Statement
(Loc
,
1953 Expression
=> New_Copy_Tree
(Discriminant_Value
));
1955 Set_No_Ctrl_Actions
(Instr
);
1956 Append_To
(L
, Instr
);
1958 Next_Stored_Discriminant
(Discriminant
);
1964 -- Generate the assignments, component by component
1966 -- tmp.comp1 := Expr1_From_Aggr;
1967 -- tmp.comp2 := Expr2_From_Aggr;
1970 Comp
:= First
(Component_Associations
(N
));
1971 while Present
(Comp
) loop
1972 Selector
:= Entity
(First
(Choices
(Comp
)));
1974 -- Ada 2005 (AI-287): Default initialization of a limited component
1976 if Box_Present
(Comp
)
1977 and then Is_Limited_Type
(Etype
(Selector
))
1979 -- Ada 2005 (AI-287): If the component type has tasks then
1980 -- generate the activation chain and master entities (except
1981 -- in case of an allocator because in that case these entities
1982 -- are generated by Build_Task_Allocate_Block_With_Init_Stmts).
1985 Ctype
: constant Entity_Id
:= Etype
(Selector
);
1986 Inside_Allocator
: Boolean := False;
1987 P
: Node_Id
:= Parent
(N
);
1990 if Is_Task_Type
(Ctype
) or else Has_Task
(Ctype
) then
1991 while Present
(P
) loop
1992 if Nkind
(P
) = N_Allocator
then
1993 Inside_Allocator
:= True;
2000 if not Inside_Init_Proc
and not Inside_Allocator
then
2001 Build_Activation_Chain_Entity
(N
);
2003 if not Has_Master_Entity
(Current_Scope
) then
2004 Build_Master_Entity
(Etype
(N
));
2011 Build_Initialization_Call
(Loc
,
2012 Id_Ref
=> Make_Selected_Component
(Loc
,
2013 Prefix
=> New_Copy_Tree
(Target
),
2014 Selector_Name
=> New_Occurrence_Of
(Selector
,
2016 Typ
=> Etype
(Selector
),
2017 With_Default_Init
=> True));
2024 if Ekind
(Selector
) /= E_Discriminant
2025 or else Nkind
(N
) = N_Extension_Aggregate
2027 Comp_Type
:= Etype
(Selector
);
2029 Make_Selected_Component
(Loc
,
2030 Prefix
=> New_Copy_Tree
(Target
),
2031 Selector_Name
=> New_Occurrence_Of
(Selector
, Loc
));
2033 if Nkind
(Expression
(Comp
)) = N_Qualified_Expression
then
2034 Expr_Q
:= Expression
(Expression
(Comp
));
2036 Expr_Q
:= Expression
(Comp
);
2039 -- The controller is the one of the parent type defining
2040 -- the component (in case of inherited components).
2042 if Controlled_Type
(Comp_Type
) then
2043 Internal_Final_List
:=
2044 Make_Selected_Component
(Loc
,
2045 Prefix
=> Convert_To
(
2046 Scope
(Original_Record_Component
(Selector
)),
2047 New_Copy_Tree
(Target
)),
2049 Make_Identifier
(Loc
, Name_uController
));
2051 Internal_Final_List
:=
2052 Make_Selected_Component
(Loc
,
2053 Prefix
=> Internal_Final_List
,
2054 Selector_Name
=> Make_Identifier
(Loc
, Name_F
));
2056 -- The internal final list can be part of a constant object
2058 Set_Assignment_OK
(Internal_Final_List
);
2061 Internal_Final_List
:= Empty
;
2066 if Is_Delayed_Aggregate
(Expr_Q
) then
2068 Late_Expansion
(Expr_Q
, Comp_Type
, Comp_Expr
,
2069 Internal_Final_List
));
2073 Make_OK_Assignment_Statement
(Loc
,
2075 Expression
=> Expression
(Comp
));
2077 Set_No_Ctrl_Actions
(Instr
);
2078 Append_To
(L
, Instr
);
2080 -- Adjust the tag if tagged (because of possible view
2081 -- conversions), unless compiling for the Java VM
2082 -- where tags are implicit.
2084 -- tmp.comp._tag := comp_typ'tag;
2086 if Is_Tagged_Type
(Comp_Type
) and then not Java_VM
then
2088 Make_OK_Assignment_Statement
(Loc
,
2090 Make_Selected_Component
(Loc
,
2091 Prefix
=> New_Copy_Tree
(Comp_Expr
),
2093 New_Reference_To
(Tag_Component
(Comp_Type
), Loc
)),
2096 Unchecked_Convert_To
(RTE
(RE_Tag
),
2098 Access_Disp_Table
(Comp_Type
), Loc
)));
2100 Append_To
(L
, Instr
);
2103 -- Adjust and Attach the component to the proper controller
2104 -- Adjust (tmp.comp);
2105 -- Attach_To_Final_List (tmp.comp,
2106 -- comp_typ (tmp)._record_controller.f)
2108 if Controlled_Type
(Comp_Type
) then
2111 Ref
=> New_Copy_Tree
(Comp_Expr
),
2113 Flist_Ref
=> Internal_Final_List
,
2114 With_Attach
=> Make_Integer_Literal
(Loc
, 1)));
2120 elsif Ekind
(Selector
) = E_Discriminant
2121 and then Nkind
(N
) /= N_Extension_Aggregate
2122 and then Nkind
(Parent
(N
)) = N_Component_Association
2123 and then Is_Constrained
(Typ
)
2125 -- We must check that the discriminant value imposed by the
2126 -- context is the same as the value given in the subaggregate,
2127 -- because after the expansion into assignments there is no
2128 -- record on which to perform a regular discriminant check.
2135 D_Val
:= First_Elmt
(Discriminant_Constraint
(Typ
));
2136 Disc
:= First_Discriminant
(Typ
);
2138 while Chars
(Disc
) /= Chars
(Selector
) loop
2139 Next_Discriminant
(Disc
);
2143 pragma Assert
(Present
(D_Val
));
2146 Make_Raise_Constraint_Error
(Loc
,
2149 Left_Opnd
=> New_Copy_Tree
(Node
(D_Val
)),
2150 Right_Opnd
=> Expression
(Comp
)),
2151 Reason
=> CE_Discriminant_Check_Failed
));
2160 -- If the type is tagged, the tag needs to be initialized (unless
2161 -- compiling for the Java VM where tags are implicit). It is done
2162 -- late in the initialization process because in some cases, we call
2163 -- the init proc of an ancestor which will not leave out the right tag
2165 if Ancestor_Is_Expression
then
2168 elsif Is_Tagged_Type
(Typ
) and then not Java_VM
then
2170 Make_OK_Assignment_Statement
(Loc
,
2172 Make_Selected_Component
(Loc
,
2173 Prefix
=> New_Copy_Tree
(Target
),
2175 New_Reference_To
(Tag_Component
(Base_Type
(Typ
)), Loc
)),
2178 Unchecked_Convert_To
(RTE
(RE_Tag
),
2179 New_Reference_To
(Access_Disp_Table
(Base_Type
(Typ
)), Loc
)));
2181 Append_To
(L
, Instr
);
2184 -- Now deal with the various controlled type data structure
2188 and then Finalize_Storage_Only
(Typ
)
2189 and then (Is_Library_Level_Entity
(Obj
)
2190 or else Entity
(Constant_Value
(RTE
(RE_Garbage_Collected
)))
2193 Attach
:= Make_Integer_Literal
(Loc
, 0);
2195 elsif Nkind
(Parent
(N
)) = N_Qualified_Expression
2196 and then Nkind
(Parent
(Parent
(N
))) = N_Allocator
2198 Attach
:= Make_Integer_Literal
(Loc
, 2);
2201 Attach
:= Make_Integer_Literal
(Loc
, 1);
2204 -- Determine the external finalization list. It is either the
2205 -- finalization list of the outer-scope or the one coming from
2206 -- an outer aggregate. When the target is not a temporary, the
2207 -- proper scope is the scope of the target rather than the
2208 -- potentially transient current scope.
2210 if Controlled_Type
(Typ
) then
2211 if Present
(Flist
) then
2212 External_Final_List
:= New_Copy_Tree
(Flist
);
2214 elsif Is_Entity_Name
(Target
)
2215 and then Present
(Scope
(Entity
(Target
)))
2217 External_Final_List
:= Find_Final_List
(Scope
(Entity
(Target
)));
2220 External_Final_List
:= Find_Final_List
(Current_Scope
);
2224 External_Final_List
:= Empty
;
2227 -- Initialize and attach the outer object in the is_controlled case
2229 if Is_Controlled
(Typ
) then
2230 if Ancestor_Is_Subtype_Mark
then
2231 Ref
:= Convert_To
(Init_Typ
, New_Copy_Tree
(Target
));
2232 Set_Assignment_OK
(Ref
);
2234 Make_Procedure_Call_Statement
(Loc
,
2235 Name
=> New_Reference_To
(
2236 Find_Prim_Op
(Init_Typ
, Name_Initialize
), Loc
),
2237 Parameter_Associations
=> New_List
(New_Copy_Tree
(Ref
))));
2240 if not Has_Controlled_Component
(Typ
) then
2241 Ref
:= New_Copy_Tree
(Target
);
2242 Set_Assignment_OK
(Ref
);
2246 Flist_Ref
=> New_Copy_Tree
(External_Final_List
),
2247 With_Attach
=> Attach
));
2251 -- In the Has_Controlled component case, all the intermediate
2252 -- controllers must be initialized
2254 if Has_Controlled_Component
(Typ
)
2255 and not Is_Limited_Ancestor_Expansion
2258 Inner_Typ
: Entity_Id
;
2259 Outer_Typ
: Entity_Id
;
2264 Outer_Typ
:= Base_Type
(Typ
);
2266 -- Find outer type with a controller
2268 while Outer_Typ
/= Init_Typ
2269 and then not Has_New_Controlled_Component
(Outer_Typ
)
2271 Outer_Typ
:= Etype
(Outer_Typ
);
2274 -- Attach it to the outer record controller to the
2275 -- external final list
2277 if Outer_Typ
= Init_Typ
then
2278 Append_List_To
(Start_L
,
2282 F
=> External_Final_List
,
2284 Init_Pr
=> Ancestor_Is_Expression
));
2287 Inner_Typ
:= Init_Typ
;
2290 Append_List_To
(Start_L
,
2294 F
=> External_Final_List
,
2298 Inner_Typ
:= Etype
(Outer_Typ
);
2300 not Is_Tagged_Type
(Typ
) or else Inner_Typ
= Outer_Typ
;
2303 -- The outer object has to be attached as well
2305 if Is_Controlled
(Typ
) then
2306 Ref
:= New_Copy_Tree
(Target
);
2307 Set_Assignment_OK
(Ref
);
2311 Flist_Ref
=> New_Copy_Tree
(External_Final_List
),
2312 With_Attach
=> New_Copy_Tree
(Attach
)));
2315 -- Initialize the internal controllers for tagged types with
2316 -- more than one controller.
2318 while not At_Root
and then Inner_Typ
/= Init_Typ
loop
2319 if Has_New_Controlled_Component
(Inner_Typ
) then
2321 Make_Selected_Component
(Loc
,
2322 Prefix
=> Convert_To
(Outer_Typ
, New_Copy_Tree
(Target
)),
2324 Make_Identifier
(Loc
, Name_uController
));
2326 Make_Selected_Component
(Loc
,
2328 Selector_Name
=> Make_Identifier
(Loc
, Name_F
));
2330 Append_List_To
(Start_L
,
2335 Attach
=> Make_Integer_Literal
(Loc
, 1),
2337 Outer_Typ
:= Inner_Typ
;
2342 At_Root
:= Inner_Typ
= Etype
(Inner_Typ
);
2343 Inner_Typ
:= Etype
(Inner_Typ
);
2346 -- If not done yet attach the controller of the ancestor part
2348 if Outer_Typ
/= Init_Typ
2349 and then Inner_Typ
= Init_Typ
2350 and then Has_Controlled_Component
(Init_Typ
)
2353 Make_Selected_Component
(Loc
,
2354 Prefix
=> Convert_To
(Outer_Typ
, New_Copy_Tree
(Target
)),
2355 Selector_Name
=> Make_Identifier
(Loc
, Name_uController
));
2357 Make_Selected_Component
(Loc
,
2359 Selector_Name
=> Make_Identifier
(Loc
, Name_F
));
2361 Attach
:= Make_Integer_Literal
(Loc
, 1);
2362 Append_List_To
(Start_L
,
2368 Init_Pr
=> Ancestor_Is_Expression
));
2373 Append_List_To
(Start_L
, L
);
2375 end Build_Record_Aggr_Code
;
2377 -------------------------------
2378 -- Convert_Aggr_In_Allocator --
2379 -------------------------------
2381 procedure Convert_Aggr_In_Allocator
(Decl
, Aggr
: Node_Id
) is
2382 Loc
: constant Source_Ptr
:= Sloc
(Aggr
);
2383 Typ
: constant Entity_Id
:= Etype
(Aggr
);
2384 Temp
: constant Entity_Id
:= Defining_Identifier
(Decl
);
2386 Occ
: constant Node_Id
:=
2387 Unchecked_Convert_To
(Typ
,
2388 Make_Explicit_Dereference
(Loc
,
2389 New_Reference_To
(Temp
, Loc
)));
2391 Access_Type
: constant Entity_Id
:= Etype
(Temp
);
2394 if Is_Array_Type
(Typ
) then
2395 Convert_Array_Aggr_In_Allocator
(Decl
, Aggr
, Occ
);
2397 elsif Has_Default_Init_Comps
(Aggr
) then
2399 L
: constant List_Id
:= New_List
;
2400 Init_Stmts
: List_Id
;
2403 Init_Stmts
:= Late_Expansion
(Aggr
, Typ
, Occ
,
2404 Find_Final_List
(Access_Type
),
2405 Associated_Final_Chain
(Base_Type
(Access_Type
)));
2407 Build_Task_Allocate_Block_With_Init_Stmts
(L
, Aggr
, Init_Stmts
);
2408 Insert_Actions_After
(Decl
, L
);
2412 Insert_Actions_After
(Decl
,
2413 Late_Expansion
(Aggr
, Typ
, Occ
,
2414 Find_Final_List
(Access_Type
),
2415 Associated_Final_Chain
(Base_Type
(Access_Type
))));
2417 end Convert_Aggr_In_Allocator
;
2419 --------------------------------
2420 -- Convert_Aggr_In_Assignment --
2421 --------------------------------
2423 procedure Convert_Aggr_In_Assignment
(N
: Node_Id
) is
2424 Aggr
: Node_Id
:= Expression
(N
);
2425 Typ
: constant Entity_Id
:= Etype
(Aggr
);
2426 Occ
: constant Node_Id
:= New_Copy_Tree
(Name
(N
));
2429 if Nkind
(Aggr
) = N_Qualified_Expression
then
2430 Aggr
:= Expression
(Aggr
);
2433 Insert_Actions_After
(N
,
2434 Late_Expansion
(Aggr
, Typ
, Occ
,
2435 Find_Final_List
(Typ
, New_Copy_Tree
(Occ
))));
2436 end Convert_Aggr_In_Assignment
;
2438 ---------------------------------
2439 -- Convert_Aggr_In_Object_Decl --
2440 ---------------------------------
2442 procedure Convert_Aggr_In_Object_Decl
(N
: Node_Id
) is
2443 Obj
: constant Entity_Id
:= Defining_Identifier
(N
);
2444 Aggr
: Node_Id
:= Expression
(N
);
2445 Loc
: constant Source_Ptr
:= Sloc
(Aggr
);
2446 Typ
: constant Entity_Id
:= Etype
(Aggr
);
2447 Occ
: constant Node_Id
:= New_Occurrence_Of
(Obj
, Loc
);
2449 function Discriminants_Ok
return Boolean;
2450 -- If the object type is constrained, the discriminants in the
2451 -- aggregate must be checked against the discriminants of the subtype.
2452 -- This cannot be done using Apply_Discriminant_Checks because after
2453 -- expansion there is no aggregate left to check.
2455 ----------------------
2456 -- Discriminants_Ok --
2457 ----------------------
2459 function Discriminants_Ok
return Boolean is
2460 Cond
: Node_Id
:= Empty
;
2469 D
:= First_Discriminant
(Typ
);
2470 Disc1
:= First_Elmt
(Discriminant_Constraint
(Typ
));
2471 Disc2
:= First_Elmt
(Discriminant_Constraint
(Etype
(Obj
)));
2473 while Present
(Disc1
) and then Present
(Disc2
) loop
2474 Val1
:= Node
(Disc1
);
2475 Val2
:= Node
(Disc2
);
2477 if not Is_OK_Static_Expression
(Val1
)
2478 or else not Is_OK_Static_Expression
(Val2
)
2480 Check
:= Make_Op_Ne
(Loc
,
2481 Left_Opnd
=> Duplicate_Subexpr
(Val1
),
2482 Right_Opnd
=> Duplicate_Subexpr
(Val2
));
2488 Cond
:= Make_Or_Else
(Loc
,
2490 Right_Opnd
=> Check
);
2493 elsif Expr_Value
(Val1
) /= Expr_Value
(Val2
) then
2494 Apply_Compile_Time_Constraint_Error
(Aggr
,
2495 Msg
=> "incorrect value for discriminant&?",
2496 Reason
=> CE_Discriminant_Check_Failed
,
2501 Next_Discriminant
(D
);
2506 -- If any discriminant constraint is non-static, emit a check
2508 if Present
(Cond
) then
2510 Make_Raise_Constraint_Error
(Loc
,
2512 Reason
=> CE_Discriminant_Check_Failed
));
2516 end Discriminants_Ok
;
2518 -- Start of processing for Convert_Aggr_In_Object_Decl
2521 Set_Assignment_OK
(Occ
);
2523 if Nkind
(Aggr
) = N_Qualified_Expression
then
2524 Aggr
:= Expression
(Aggr
);
2527 if Has_Discriminants
(Typ
)
2528 and then Typ
/= Etype
(Obj
)
2529 and then Is_Constrained
(Etype
(Obj
))
2530 and then not Discriminants_Ok
2535 Insert_Actions_After
(N
, Late_Expansion
(Aggr
, Typ
, Occ
, Obj
=> Obj
));
2536 Set_No_Initialization
(N
);
2537 Initialize_Discriminants
(N
, Typ
);
2538 end Convert_Aggr_In_Object_Decl
;
2540 -------------------------------------
2541 -- Convert_array_Aggr_In_Allocator --
2542 -------------------------------------
2544 procedure Convert_Array_Aggr_In_Allocator
2549 Aggr_Code
: List_Id
;
2550 Typ
: constant Entity_Id
:= Etype
(Aggr
);
2551 Ctyp
: constant Entity_Id
:= Component_Type
(Typ
);
2554 -- The target is an explicit dereference of the allocated object.
2555 -- Generate component assignments to it, as for an aggregate that
2556 -- appears on the right-hand side of an assignment statement.
2559 Build_Array_Aggr_Code
(Aggr
,
2561 Index
=> First_Index
(Typ
),
2563 Scalar_Comp
=> Is_Scalar_Type
(Ctyp
));
2565 Insert_Actions_After
(Decl
, Aggr_Code
);
2566 end Convert_Array_Aggr_In_Allocator
;
2568 ----------------------------
2569 -- Convert_To_Assignments --
2570 ----------------------------
2572 procedure Convert_To_Assignments
(N
: Node_Id
; Typ
: Entity_Id
) is
2573 Loc
: constant Source_Ptr
:= Sloc
(N
);
2577 Target_Expr
: Node_Id
;
2578 Parent_Kind
: Node_Kind
;
2579 Unc_Decl
: Boolean := False;
2580 Parent_Node
: Node_Id
;
2583 Parent_Node
:= Parent
(N
);
2584 Parent_Kind
:= Nkind
(Parent_Node
);
2586 if Parent_Kind
= N_Qualified_Expression
then
2588 -- Check if we are in a unconstrained declaration because in this
2589 -- case the current delayed expansion mechanism doesn't work when
2590 -- the declared object size depend on the initializing expr.
2593 Parent_Node
:= Parent
(Parent_Node
);
2594 Parent_Kind
:= Nkind
(Parent_Node
);
2596 if Parent_Kind
= N_Object_Declaration
then
2598 not Is_Entity_Name
(Object_Definition
(Parent_Node
))
2599 or else Has_Discriminants
2600 (Entity
(Object_Definition
(Parent_Node
)))
2601 or else Is_Class_Wide_Type
2602 (Entity
(Object_Definition
(Parent_Node
)));
2607 -- Just set the Delay flag in the following cases where the
2608 -- transformation will be done top down from above
2610 -- - internal aggregate (transformed when expanding the parent)
2611 -- - allocators (see Convert_Aggr_In_Allocator)
2612 -- - object decl (see Convert_Aggr_In_Object_Decl)
2613 -- - safe assignments (see Convert_Aggr_Assignments)
2614 -- so far only the assignments in the init procs are taken
2617 if Parent_Kind
= N_Aggregate
2618 or else Parent_Kind
= N_Extension_Aggregate
2619 or else Parent_Kind
= N_Component_Association
2620 or else Parent_Kind
= N_Allocator
2621 or else (Parent_Kind
= N_Object_Declaration
and then not Unc_Decl
)
2622 or else (Parent_Kind
= N_Assignment_Statement
2623 and then Inside_Init_Proc
)
2625 Set_Expansion_Delayed
(N
);
2629 if Requires_Transient_Scope
(Typ
) then
2630 Establish_Transient_Scope
(N
, Sec_Stack
=>
2631 Is_Controlled
(Typ
) or else Has_Controlled_Component
(Typ
));
2634 -- Create the temporary
2636 Temp
:= Make_Defining_Identifier
(Loc
, New_Internal_Name
('A'));
2639 Make_Object_Declaration
(Loc
,
2640 Defining_Identifier
=> Temp
,
2641 Object_Definition
=> New_Occurrence_Of
(Typ
, Loc
));
2643 Set_No_Initialization
(Instr
);
2644 Insert_Action
(N
, Instr
);
2645 Initialize_Discriminants
(Instr
, Typ
);
2646 Target_Expr
:= New_Occurrence_Of
(Temp
, Loc
);
2648 Insert_Actions
(N
, Build_Record_Aggr_Code
(N
, Typ
, Target_Expr
));
2649 Rewrite
(N
, New_Occurrence_Of
(Temp
, Loc
));
2650 Analyze_And_Resolve
(N
, Typ
);
2651 end Convert_To_Assignments
;
2653 ---------------------------
2654 -- Convert_To_Positional --
2655 ---------------------------
2657 procedure Convert_To_Positional
2659 Max_Others_Replicate
: Nat
:= 5;
2660 Handle_Bit_Packed
: Boolean := False)
2662 Typ
: constant Entity_Id
:= Etype
(N
);
2667 Ixb
: Node_Id
) return Boolean;
2668 -- Convert the aggregate into a purely positional form if possible
2670 function Is_Flat
(N
: Node_Id
; Dims
: Int
) return Boolean;
2671 -- Return True iff the array N is flat (which is not rivial
2672 -- in the case of multidimensionsl aggregates).
2681 Ixb
: Node_Id
) return Boolean
2683 Loc
: constant Source_Ptr
:= Sloc
(N
);
2684 Blo
: constant Node_Id
:= Type_Low_Bound
(Etype
(Ixb
));
2685 Lo
: constant Node_Id
:= Type_Low_Bound
(Etype
(Ix
));
2686 Hi
: constant Node_Id
:= Type_High_Bound
(Etype
(Ix
));
2690 -- The following constant determines the maximum size of an
2691 -- aggregate produced by converting named to positional
2692 -- notation (e.g. from others clauses). This avoids running
2693 -- away with attempts to convert huge aggregates.
2695 -- The normal limit is 5000, but we increase this limit to
2696 -- 2**24 (about 16 million) if Restrictions (No_Elaboration_Code)
2697 -- or Restrictions (No_Implicit_Loops) is specified, since in
2698 -- either case, we are at risk of declaring the program illegal
2699 -- because of this limit.
2701 Max_Aggr_Size
: constant Nat
:=
2702 5000 + (2 ** 24 - 5000) *
2704 (Restriction_Active
(No_Elaboration_Code
)
2706 Restriction_Active
(No_Implicit_Loops
));
2709 if Nkind
(Original_Node
(N
)) = N_String_Literal
then
2713 -- Bounds need to be known at compile time
2715 if not Compile_Time_Known_Value
(Lo
)
2716 or else not Compile_Time_Known_Value
(Hi
)
2721 -- Get bounds and check reasonable size (positive, not too large)
2722 -- Also only handle bounds starting at the base type low bound
2723 -- for now since the compiler isn't able to handle different low
2724 -- bounds yet. Case such as new String'(3..5 => ' ') will get
2725 -- the wrong bounds, though it seems that the aggregate should
2726 -- retain the bounds set on its Etype (see C64103E and CC1311B).
2728 Lov
:= Expr_Value
(Lo
);
2729 Hiv
:= Expr_Value
(Hi
);
2732 or else (Hiv
- Lov
> Max_Aggr_Size
)
2733 or else not Compile_Time_Known_Value
(Blo
)
2734 or else (Lov
/= Expr_Value
(Blo
))
2739 -- Bounds must be in integer range (for array Vals below)
2741 if not UI_Is_In_Int_Range
(Lov
)
2743 not UI_Is_In_Int_Range
(Hiv
)
2748 -- Determine if set of alternatives is suitable for conversion
2749 -- and build an array containing the values in sequence.
2752 Vals
: array (UI_To_Int
(Lov
) .. UI_To_Int
(Hiv
))
2753 of Node_Id
:= (others => Empty
);
2754 -- The values in the aggregate sorted appropriately
2757 -- Same data as Vals in list form
2760 -- Used to validate Max_Others_Replicate limit
2763 Num
: Int
:= UI_To_Int
(Lov
);
2768 if Present
(Expressions
(N
)) then
2769 Elmt
:= First
(Expressions
(N
));
2771 while Present
(Elmt
) loop
2772 if Nkind
(Elmt
) = N_Aggregate
2773 and then Present
(Next_Index
(Ix
))
2775 not Flatten
(Elmt
, Next_Index
(Ix
), Next_Index
(Ixb
))
2780 Vals
(Num
) := Relocate_Node
(Elmt
);
2787 if No
(Component_Associations
(N
)) then
2791 Elmt
:= First
(Component_Associations
(N
));
2793 if Nkind
(Expression
(Elmt
)) = N_Aggregate
then
2794 if Present
(Next_Index
(Ix
))
2797 (Expression
(Elmt
), Next_Index
(Ix
), Next_Index
(Ixb
))
2803 Component_Loop
: while Present
(Elmt
) loop
2804 Choice
:= First
(Choices
(Elmt
));
2805 Choice_Loop
: while Present
(Choice
) loop
2807 -- If we have an others choice, fill in the missing elements
2808 -- subject to the limit established by Max_Others_Replicate.
2810 if Nkind
(Choice
) = N_Others_Choice
then
2813 for J
in Vals
'Range loop
2814 if No
(Vals
(J
)) then
2815 Vals
(J
) := New_Copy_Tree
(Expression
(Elmt
));
2816 Rep_Count
:= Rep_Count
+ 1;
2818 -- Check for maximum others replication. Note that
2819 -- we skip this test if either of the restrictions
2820 -- No_Elaboration_Code or No_Implicit_Loops is
2821 -- active, or if this is a preelaborable unit.
2824 P
: constant Entity_Id
:=
2825 Cunit_Entity
(Current_Sem_Unit
);
2828 if Restriction_Active
(No_Elaboration_Code
)
2829 or else Restriction_Active
(No_Implicit_Loops
)
2830 or else Is_Preelaborated
(P
)
2831 or else (Ekind
(P
) = E_Package_Body
2833 Is_Preelaborated
(Spec_Entity
(P
)))
2837 elsif Rep_Count
> Max_Others_Replicate
then
2844 exit Component_Loop
;
2846 -- Case of a subtype mark
2848 elsif Nkind
(Choice
) = N_Identifier
2849 and then Is_Type
(Entity
(Choice
))
2851 Lo
:= Type_Low_Bound
(Etype
(Choice
));
2852 Hi
:= Type_High_Bound
(Etype
(Choice
));
2854 -- Case of subtype indication
2856 elsif Nkind
(Choice
) = N_Subtype_Indication
then
2857 Lo
:= Low_Bound
(Range_Expression
(Constraint
(Choice
)));
2858 Hi
:= High_Bound
(Range_Expression
(Constraint
(Choice
)));
2862 elsif Nkind
(Choice
) = N_Range
then
2863 Lo
:= Low_Bound
(Choice
);
2864 Hi
:= High_Bound
(Choice
);
2866 -- Normal subexpression case
2868 else pragma Assert
(Nkind
(Choice
) in N_Subexpr
);
2869 if not Compile_Time_Known_Value
(Choice
) then
2873 Vals
(UI_To_Int
(Expr_Value
(Choice
))) :=
2874 New_Copy_Tree
(Expression
(Elmt
));
2879 -- Range cases merge with Lo,Hi said
2881 if not Compile_Time_Known_Value
(Lo
)
2883 not Compile_Time_Known_Value
(Hi
)
2887 for J
in UI_To_Int
(Expr_Value
(Lo
)) ..
2888 UI_To_Int
(Expr_Value
(Hi
))
2890 Vals
(J
) := New_Copy_Tree
(Expression
(Elmt
));
2896 end loop Choice_Loop
;
2899 end loop Component_Loop
;
2901 -- If we get here the conversion is possible
2904 for J
in Vals
'Range loop
2905 Append
(Vals
(J
), Vlist
);
2908 Rewrite
(N
, Make_Aggregate
(Loc
, Expressions
=> Vlist
));
2909 Set_Aggregate_Bounds
(N
, Aggregate_Bounds
(Original_Node
(N
)));
2918 function Is_Flat
(N
: Node_Id
; Dims
: Int
) return Boolean is
2925 elsif Nkind
(N
) = N_Aggregate
then
2926 if Present
(Component_Associations
(N
)) then
2930 Elmt
:= First
(Expressions
(N
));
2932 while Present
(Elmt
) loop
2933 if not Is_Flat
(Elmt
, Dims
- 1) then
2947 -- Start of processing for Convert_To_Positional
2950 -- Ada 2005 (AI-287): Do not convert in case of default initialized
2951 -- components because in this case will need to call the corresponding
2954 if Has_Default_Init_Comps
(N
) then
2958 if Is_Flat
(N
, Number_Dimensions
(Typ
)) then
2962 if Is_Bit_Packed_Array
(Typ
)
2963 and then not Handle_Bit_Packed
2968 -- Do not convert to positional if controlled components are
2969 -- involved since these require special processing
2971 if Has_Controlled_Component
(Typ
) then
2975 if Flatten
(N
, First_Index
(Typ
), First_Index
(Base_Type
(Typ
))) then
2976 Analyze_And_Resolve
(N
, Typ
);
2978 end Convert_To_Positional
;
2980 ----------------------------
2981 -- Expand_Array_Aggregate --
2982 ----------------------------
2984 -- Array aggregate expansion proceeds as follows:
2986 -- 1. If requested we generate code to perform all the array aggregate
2987 -- bound checks, specifically
2989 -- (a) Check that the index range defined by aggregate bounds is
2990 -- compatible with corresponding index subtype.
2992 -- (b) If an others choice is present check that no aggregate
2993 -- index is outside the bounds of the index constraint.
2995 -- (c) For multidimensional arrays make sure that all subaggregates
2996 -- corresponding to the same dimension have the same bounds.
2998 -- 2. Check for packed array aggregate which can be converted to a
2999 -- constant so that the aggregate disappeares completely.
3001 -- 3. Check case of nested aggregate. Generally nested aggregates are
3002 -- handled during the processing of the parent aggregate.
3004 -- 4. Check if the aggregate can be statically processed. If this is the
3005 -- case pass it as is to Gigi. Note that a necessary condition for
3006 -- static processing is that the aggregate be fully positional.
3008 -- 5. If in place aggregate expansion is possible (i.e. no need to create
3009 -- a temporary) then mark the aggregate as such and return. Otherwise
3010 -- create a new temporary and generate the appropriate initialization
3013 procedure Expand_Array_Aggregate
(N
: Node_Id
) is
3014 Loc
: constant Source_Ptr
:= Sloc
(N
);
3016 Typ
: constant Entity_Id
:= Etype
(N
);
3017 Ctyp
: constant Entity_Id
:= Component_Type
(Typ
);
3018 -- Typ is the correct constrained array subtype of the aggregate
3019 -- Ctyp is the corresponding component type.
3021 Aggr_Dimension
: constant Pos
:= Number_Dimensions
(Typ
);
3022 -- Number of aggregate index dimensions
3024 Aggr_Low
: array (1 .. Aggr_Dimension
) of Node_Id
;
3025 Aggr_High
: array (1 .. Aggr_Dimension
) of Node_Id
;
3026 -- Low and High bounds of the constraint for each aggregate index
3028 Aggr_Index_Typ
: array (1 .. Aggr_Dimension
) of Entity_Id
;
3029 -- The type of each index
3031 Maybe_In_Place_OK
: Boolean;
3032 -- If the type is neither controlled nor packed and the aggregate
3033 -- is the expression in an assignment, assignment in place may be
3034 -- possible, provided other conditions are met on the LHS.
3036 Others_Present
: array (1 .. Aggr_Dimension
) of Boolean :=
3038 -- If Others_Present (J) is True, then there is an others choice
3039 -- in one of the sub-aggregates of N at dimension J.
3041 procedure Build_Constrained_Type
(Positional
: Boolean);
3042 -- If the subtype is not static or unconstrained, build a constrained
3043 -- type using the computable sizes of the aggregate and its sub-
3046 procedure Check_Bounds
(Aggr_Bounds
: Node_Id
; Index_Bounds
: Node_Id
);
3047 -- Checks that the bounds of Aggr_Bounds are within the bounds defined
3050 procedure Check_Same_Aggr_Bounds
(Sub_Aggr
: Node_Id
; Dim
: Pos
);
3051 -- Checks that in a multi-dimensional array aggregate all subaggregates
3052 -- corresponding to the same dimension have the same bounds.
3053 -- Sub_Aggr is an array sub-aggregate. Dim is the dimension
3054 -- corresponding to the sub-aggregate.
3056 procedure Compute_Others_Present
(Sub_Aggr
: Node_Id
; Dim
: Pos
);
3057 -- Computes the values of array Others_Present. Sub_Aggr is the
3058 -- array sub-aggregate we start the computation from. Dim is the
3059 -- dimension corresponding to the sub-aggregate.
3061 function Has_Address_Clause
(D
: Node_Id
) return Boolean;
3062 -- If the aggregate is the expression in an object declaration, it
3063 -- cannot be expanded in place. This function does a lookahead in the
3064 -- current declarative part to find an address clause for the object
3067 function In_Place_Assign_OK
return Boolean;
3068 -- Simple predicate to determine whether an aggregate assignment can
3069 -- be done in place, because none of the new values can depend on the
3070 -- components of the target of the assignment.
3072 procedure Others_Check
(Sub_Aggr
: Node_Id
; Dim
: Pos
);
3073 -- Checks that if an others choice is present in any sub-aggregate no
3074 -- aggregate index is outside the bounds of the index constraint.
3075 -- Sub_Aggr is an array sub-aggregate. Dim is the dimension
3076 -- corresponding to the sub-aggregate.
3078 ----------------------------
3079 -- Build_Constrained_Type --
3080 ----------------------------
3082 procedure Build_Constrained_Type
(Positional
: Boolean) is
3083 Loc
: constant Source_Ptr
:= Sloc
(N
);
3084 Agg_Type
: Entity_Id
;
3087 Typ
: constant Entity_Id
:= Etype
(N
);
3088 Indices
: constant List_Id
:= New_List
;
3094 Make_Defining_Identifier
(
3095 Loc
, New_Internal_Name
('A'));
3097 -- If the aggregate is purely positional, all its subaggregates
3098 -- have the same size. We collect the dimensions from the first
3099 -- subaggregate at each level.
3104 for D
in 1 .. Number_Dimensions
(Typ
) loop
3105 Comp
:= First
(Expressions
(Sub_Agg
));
3110 while Present
(Comp
) loop
3117 Low_Bound
=> Make_Integer_Literal
(Loc
, 1),
3119 Make_Integer_Literal
(Loc
, Num
)),
3124 -- We know the aggregate type is unconstrained and the
3125 -- aggregate is not processable by the back end, therefore
3126 -- not necessarily positional. Retrieve the bounds of each
3127 -- dimension as computed earlier.
3129 for D
in 1 .. Number_Dimensions
(Typ
) loop
3132 Low_Bound
=> Aggr_Low
(D
),
3133 High_Bound
=> Aggr_High
(D
)),
3139 Make_Full_Type_Declaration
(Loc
,
3140 Defining_Identifier
=> Agg_Type
,
3142 Make_Constrained_Array_Definition
(Loc
,
3143 Discrete_Subtype_Definitions
=> Indices
,
3144 Component_Definition
=>
3145 Make_Component_Definition
(Loc
,
3146 Aliased_Present
=> False,
3147 Subtype_Indication
=>
3148 New_Occurrence_Of
(Component_Type
(Typ
), Loc
))));
3150 Insert_Action
(N
, Decl
);
3152 Set_Etype
(N
, Agg_Type
);
3153 Set_Is_Itype
(Agg_Type
);
3154 Freeze_Itype
(Agg_Type
, N
);
3155 end Build_Constrained_Type
;
3161 procedure Check_Bounds
(Aggr_Bounds
: Node_Id
; Index_Bounds
: Node_Id
) is
3168 Cond
: Node_Id
:= Empty
;
3171 Get_Index_Bounds
(Aggr_Bounds
, Aggr_Lo
, Aggr_Hi
);
3172 Get_Index_Bounds
(Index_Bounds
, Ind_Lo
, Ind_Hi
);
3174 -- Generate the following test:
3176 -- [constraint_error when
3177 -- Aggr_Lo <= Aggr_Hi and then
3178 -- (Aggr_Lo < Ind_Lo or else Aggr_Hi > Ind_Hi)]
3180 -- As an optimization try to see if some tests are trivially vacuos
3181 -- because we are comparing an expression against itself.
3183 if Aggr_Lo
= Ind_Lo
and then Aggr_Hi
= Ind_Hi
then
3186 elsif Aggr_Hi
= Ind_Hi
then
3189 Left_Opnd
=> Duplicate_Subexpr_Move_Checks
(Aggr_Lo
),
3190 Right_Opnd
=> Duplicate_Subexpr_Move_Checks
(Ind_Lo
));
3192 elsif Aggr_Lo
= Ind_Lo
then
3195 Left_Opnd
=> Duplicate_Subexpr_Move_Checks
(Aggr_Hi
),
3196 Right_Opnd
=> Duplicate_Subexpr_Move_Checks
(Ind_Hi
));
3203 Left_Opnd
=> Duplicate_Subexpr_Move_Checks
(Aggr_Lo
),
3204 Right_Opnd
=> Duplicate_Subexpr_Move_Checks
(Ind_Lo
)),
3208 Left_Opnd
=> Duplicate_Subexpr
(Aggr_Hi
),
3209 Right_Opnd
=> Duplicate_Subexpr
(Ind_Hi
)));
3212 if Present
(Cond
) then
3217 Left_Opnd
=> Duplicate_Subexpr_Move_Checks
(Aggr_Lo
),
3218 Right_Opnd
=> Duplicate_Subexpr_Move_Checks
(Aggr_Hi
)),
3220 Right_Opnd
=> Cond
);
3222 Set_Analyzed
(Left_Opnd
(Left_Opnd
(Cond
)), False);
3223 Set_Analyzed
(Right_Opnd
(Left_Opnd
(Cond
)), False);
3225 Make_Raise_Constraint_Error
(Loc
,
3227 Reason
=> CE_Length_Check_Failed
));
3231 ----------------------------
3232 -- Check_Same_Aggr_Bounds --
3233 ----------------------------
3235 procedure Check_Same_Aggr_Bounds
(Sub_Aggr
: Node_Id
; Dim
: Pos
) is
3236 Sub_Lo
: constant Node_Id
:= Low_Bound
(Aggregate_Bounds
(Sub_Aggr
));
3237 Sub_Hi
: constant Node_Id
:= High_Bound
(Aggregate_Bounds
(Sub_Aggr
));
3238 -- The bounds of this specific sub-aggregate
3240 Aggr_Lo
: constant Node_Id
:= Aggr_Low
(Dim
);
3241 Aggr_Hi
: constant Node_Id
:= Aggr_High
(Dim
);
3242 -- The bounds of the aggregate for this dimension
3244 Ind_Typ
: constant Entity_Id
:= Aggr_Index_Typ
(Dim
);
3245 -- The index type for this dimension.xxx
3247 Cond
: Node_Id
:= Empty
;
3253 -- If index checks are on generate the test
3255 -- [constraint_error when
3256 -- Aggr_Lo /= Sub_Lo or else Aggr_Hi /= Sub_Hi]
3258 -- As an optimization try to see if some tests are trivially vacuos
3259 -- because we are comparing an expression against itself. Also for
3260 -- the first dimension the test is trivially vacuous because there
3261 -- is just one aggregate for dimension 1.
3263 if Index_Checks_Suppressed
(Ind_Typ
) then
3267 or else (Aggr_Lo
= Sub_Lo
and then Aggr_Hi
= Sub_Hi
)
3271 elsif Aggr_Hi
= Sub_Hi
then
3274 Left_Opnd
=> Duplicate_Subexpr_Move_Checks
(Aggr_Lo
),
3275 Right_Opnd
=> Duplicate_Subexpr_Move_Checks
(Sub_Lo
));
3277 elsif Aggr_Lo
= Sub_Lo
then
3280 Left_Opnd
=> Duplicate_Subexpr_Move_Checks
(Aggr_Hi
),
3281 Right_Opnd
=> Duplicate_Subexpr_Move_Checks
(Sub_Hi
));
3288 Left_Opnd
=> Duplicate_Subexpr_Move_Checks
(Aggr_Lo
),
3289 Right_Opnd
=> Duplicate_Subexpr_Move_Checks
(Sub_Lo
)),
3293 Left_Opnd
=> Duplicate_Subexpr
(Aggr_Hi
),
3294 Right_Opnd
=> Duplicate_Subexpr
(Sub_Hi
)));
3297 if Present
(Cond
) then
3299 Make_Raise_Constraint_Error
(Loc
,
3301 Reason
=> CE_Length_Check_Failed
));
3304 -- Now look inside the sub-aggregate to see if there is more work
3306 if Dim
< Aggr_Dimension
then
3308 -- Process positional components
3310 if Present
(Expressions
(Sub_Aggr
)) then
3311 Expr
:= First
(Expressions
(Sub_Aggr
));
3312 while Present
(Expr
) loop
3313 Check_Same_Aggr_Bounds
(Expr
, Dim
+ 1);
3318 -- Process component associations
3320 if Present
(Component_Associations
(Sub_Aggr
)) then
3321 Assoc
:= First
(Component_Associations
(Sub_Aggr
));
3322 while Present
(Assoc
) loop
3323 Expr
:= Expression
(Assoc
);
3324 Check_Same_Aggr_Bounds
(Expr
, Dim
+ 1);
3329 end Check_Same_Aggr_Bounds
;
3331 ----------------------------
3332 -- Compute_Others_Present --
3333 ----------------------------
3335 procedure Compute_Others_Present
(Sub_Aggr
: Node_Id
; Dim
: Pos
) is
3340 if Present
(Component_Associations
(Sub_Aggr
)) then
3341 Assoc
:= Last
(Component_Associations
(Sub_Aggr
));
3343 if Nkind
(First
(Choices
(Assoc
))) = N_Others_Choice
then
3344 Others_Present
(Dim
) := True;
3348 -- Now look inside the sub-aggregate to see if there is more work
3350 if Dim
< Aggr_Dimension
then
3352 -- Process positional components
3354 if Present
(Expressions
(Sub_Aggr
)) then
3355 Expr
:= First
(Expressions
(Sub_Aggr
));
3356 while Present
(Expr
) loop
3357 Compute_Others_Present
(Expr
, Dim
+ 1);
3362 -- Process component associations
3364 if Present
(Component_Associations
(Sub_Aggr
)) then
3365 Assoc
:= First
(Component_Associations
(Sub_Aggr
));
3366 while Present
(Assoc
) loop
3367 Expr
:= Expression
(Assoc
);
3368 Compute_Others_Present
(Expr
, Dim
+ 1);
3373 end Compute_Others_Present
;
3375 ------------------------
3376 -- Has_Address_Clause --
3377 ------------------------
3379 function Has_Address_Clause
(D
: Node_Id
) return Boolean is
3380 Id
: constant Entity_Id
:= Defining_Identifier
(D
);
3381 Decl
: Node_Id
:= Next
(D
);
3384 while Present
(Decl
) loop
3385 if Nkind
(Decl
) = N_At_Clause
3386 and then Chars
(Identifier
(Decl
)) = Chars
(Id
)
3390 elsif Nkind
(Decl
) = N_Attribute_Definition_Clause
3391 and then Chars
(Decl
) = Name_Address
3392 and then Chars
(Name
(Decl
)) = Chars
(Id
)
3401 end Has_Address_Clause
;
3403 ------------------------
3404 -- In_Place_Assign_OK --
3405 ------------------------
3407 function In_Place_Assign_OK
return Boolean is
3415 function Is_Others_Aggregate
(Aggr
: Node_Id
) return Boolean;
3416 -- Aggregates that consist of a single Others choice are safe
3417 -- if the single expression is.
3419 function Safe_Aggregate
(Aggr
: Node_Id
) return Boolean;
3420 -- Check recursively that each component of a (sub)aggregate does
3421 -- not depend on the variable being assigned to.
3423 function Safe_Component
(Expr
: Node_Id
) return Boolean;
3424 -- Verify that an expression cannot depend on the variable being
3425 -- assigned to. Room for improvement here (but less than before).
3427 -------------------------
3428 -- Is_Others_Aggregate --
3429 -------------------------
3431 function Is_Others_Aggregate
(Aggr
: Node_Id
) return Boolean is
3433 return No
(Expressions
(Aggr
))
3435 (First
(Choices
(First
(Component_Associations
(Aggr
)))))
3437 end Is_Others_Aggregate
;
3439 --------------------
3440 -- Safe_Aggregate --
3441 --------------------
3443 function Safe_Aggregate
(Aggr
: Node_Id
) return Boolean is
3447 if Present
(Expressions
(Aggr
)) then
3448 Expr
:= First
(Expressions
(Aggr
));
3450 while Present
(Expr
) loop
3451 if Nkind
(Expr
) = N_Aggregate
then
3452 if not Safe_Aggregate
(Expr
) then
3456 elsif not Safe_Component
(Expr
) then
3464 if Present
(Component_Associations
(Aggr
)) then
3465 Expr
:= First
(Component_Associations
(Aggr
));
3467 while Present
(Expr
) loop
3468 if Nkind
(Expression
(Expr
)) = N_Aggregate
then
3469 if not Safe_Aggregate
(Expression
(Expr
)) then
3473 elsif not Safe_Component
(Expression
(Expr
)) then
3484 --------------------
3485 -- Safe_Component --
3486 --------------------
3488 function Safe_Component
(Expr
: Node_Id
) return Boolean is
3489 Comp
: Node_Id
:= Expr
;
3491 function Check_Component
(Comp
: Node_Id
) return Boolean;
3492 -- Do the recursive traversal, after copy
3494 ---------------------
3495 -- Check_Component --
3496 ---------------------
3498 function Check_Component
(Comp
: Node_Id
) return Boolean is
3500 if Is_Overloaded
(Comp
) then
3504 return Compile_Time_Known_Value
(Comp
)
3506 or else (Is_Entity_Name
(Comp
)
3507 and then Present
(Entity
(Comp
))
3508 and then No
(Renamed_Object
(Entity
(Comp
))))
3510 or else (Nkind
(Comp
) = N_Attribute_Reference
3511 and then Check_Component
(Prefix
(Comp
)))
3513 or else (Nkind
(Comp
) in N_Binary_Op
3514 and then Check_Component
(Left_Opnd
(Comp
))
3515 and then Check_Component
(Right_Opnd
(Comp
)))
3517 or else (Nkind
(Comp
) in N_Unary_Op
3518 and then Check_Component
(Right_Opnd
(Comp
)))
3520 or else (Nkind
(Comp
) = N_Selected_Component
3521 and then Check_Component
(Prefix
(Comp
)))
3523 or else (Nkind
(Comp
) = N_Unchecked_Type_Conversion
3524 and then Check_Component
(Expression
(Comp
)));
3525 end Check_Component
;
3527 -- Start of processing for Safe_Component
3530 -- If the component appears in an association that may
3531 -- correspond to more than one element, it is not analyzed
3532 -- before the expansion into assignments, to avoid side effects.
3533 -- We analyze, but do not resolve the copy, to obtain sufficient
3534 -- entity information for the checks that follow. If component is
3535 -- overloaded we assume an unsafe function call.
3537 if not Analyzed
(Comp
) then
3538 if Is_Overloaded
(Expr
) then
3541 elsif Nkind
(Expr
) = N_Aggregate
3542 and then not Is_Others_Aggregate
(Expr
)
3546 elsif Nkind
(Expr
) = N_Allocator
then
3548 -- For now, too complex to analyze
3553 Comp
:= New_Copy_Tree
(Expr
);
3554 Set_Parent
(Comp
, Parent
(Expr
));
3558 if Nkind
(Comp
) = N_Aggregate
then
3559 return Safe_Aggregate
(Comp
);
3561 return Check_Component
(Comp
);
3565 -- Start of processing for In_Place_Assign_OK
3568 if Present
(Component_Associations
(N
)) then
3570 -- On assignment, sliding can take place, so we cannot do the
3571 -- assignment in place unless the bounds of the aggregate are
3572 -- statically equal to those of the target.
3574 -- If the aggregate is given by an others choice, the bounds
3575 -- are derived from the left-hand side, and the assignment is
3576 -- safe if the expression is.
3578 if Is_Others_Aggregate
(N
) then
3581 (Expression
(First
(Component_Associations
(N
))));
3584 Aggr_In
:= First_Index
(Etype
(N
));
3585 if Nkind
(Parent
(N
)) = N_Assignment_Statement
then
3586 Obj_In
:= First_Index
(Etype
(Name
(Parent
(N
))));
3589 -- Context is an allocator. Check bounds of aggregate
3590 -- against given type in qualified expression.
3592 pragma Assert
(Nkind
(Parent
(Parent
(N
))) = N_Allocator
);
3594 First_Index
(Etype
(Entity
(Subtype_Mark
(Parent
(N
)))));
3597 while Present
(Aggr_In
) loop
3598 Get_Index_Bounds
(Aggr_In
, Aggr_Lo
, Aggr_Hi
);
3599 Get_Index_Bounds
(Obj_In
, Obj_Lo
, Obj_Hi
);
3601 if not Compile_Time_Known_Value
(Aggr_Lo
)
3602 or else not Compile_Time_Known_Value
(Aggr_Hi
)
3603 or else not Compile_Time_Known_Value
(Obj_Lo
)
3604 or else not Compile_Time_Known_Value
(Obj_Hi
)
3605 or else Expr_Value
(Aggr_Lo
) /= Expr_Value
(Obj_Lo
)
3606 or else Expr_Value
(Aggr_Hi
) /= Expr_Value
(Obj_Hi
)
3611 Next_Index
(Aggr_In
);
3612 Next_Index
(Obj_In
);
3616 -- Now check the component values themselves
3618 return Safe_Aggregate
(N
);
3619 end In_Place_Assign_OK
;
3625 procedure Others_Check
(Sub_Aggr
: Node_Id
; Dim
: Pos
) is
3626 Aggr_Lo
: constant Node_Id
:= Aggr_Low
(Dim
);
3627 Aggr_Hi
: constant Node_Id
:= Aggr_High
(Dim
);
3628 -- The bounds of the aggregate for this dimension
3630 Ind_Typ
: constant Entity_Id
:= Aggr_Index_Typ
(Dim
);
3631 -- The index type for this dimension
3633 Need_To_Check
: Boolean := False;
3635 Choices_Lo
: Node_Id
:= Empty
;
3636 Choices_Hi
: Node_Id
:= Empty
;
3637 -- The lowest and highest discrete choices for a named sub-aggregate
3639 Nb_Choices
: Int
:= -1;
3640 -- The number of discrete non-others choices in this sub-aggregate
3642 Nb_Elements
: Uint
:= Uint_0
;
3643 -- The number of elements in a positional aggregate
3645 Cond
: Node_Id
:= Empty
;
3652 -- Check if we have an others choice. If we do make sure that this
3653 -- sub-aggregate contains at least one element in addition to the
3656 if Range_Checks_Suppressed
(Ind_Typ
) then
3657 Need_To_Check
:= False;
3659 elsif Present
(Expressions
(Sub_Aggr
))
3660 and then Present
(Component_Associations
(Sub_Aggr
))
3662 Need_To_Check
:= True;
3664 elsif Present
(Component_Associations
(Sub_Aggr
)) then
3665 Assoc
:= Last
(Component_Associations
(Sub_Aggr
));
3667 if Nkind
(First
(Choices
(Assoc
))) /= N_Others_Choice
then
3668 Need_To_Check
:= False;
3671 -- Count the number of discrete choices. Start with -1
3672 -- because the others choice does not count.
3675 Assoc
:= First
(Component_Associations
(Sub_Aggr
));
3676 while Present
(Assoc
) loop
3677 Choice
:= First
(Choices
(Assoc
));
3678 while Present
(Choice
) loop
3679 Nb_Choices
:= Nb_Choices
+ 1;
3686 -- If there is only an others choice nothing to do
3688 Need_To_Check
:= (Nb_Choices
> 0);
3692 Need_To_Check
:= False;
3695 -- If we are dealing with a positional sub-aggregate with an
3696 -- others choice then compute the number or positional elements.
3698 if Need_To_Check
and then Present
(Expressions
(Sub_Aggr
)) then
3699 Expr
:= First
(Expressions
(Sub_Aggr
));
3700 Nb_Elements
:= Uint_0
;
3701 while Present
(Expr
) loop
3702 Nb_Elements
:= Nb_Elements
+ 1;
3706 -- If the aggregate contains discrete choices and an others choice
3707 -- compute the smallest and largest discrete choice values.
3709 elsif Need_To_Check
then
3710 Compute_Choices_Lo_And_Choices_Hi
: declare
3712 Table
: Case_Table_Type
(1 .. Nb_Choices
);
3713 -- Used to sort all the different choice values
3720 Assoc
:= First
(Component_Associations
(Sub_Aggr
));
3721 while Present
(Assoc
) loop
3722 Choice
:= First
(Choices
(Assoc
));
3723 while Present
(Choice
) loop
3724 if Nkind
(Choice
) = N_Others_Choice
then
3728 Get_Index_Bounds
(Choice
, Low
, High
);
3729 Table
(J
).Choice_Lo
:= Low
;
3730 Table
(J
).Choice_Hi
:= High
;
3739 -- Sort the discrete choices
3741 Sort_Case_Table
(Table
);
3743 Choices_Lo
:= Table
(1).Choice_Lo
;
3744 Choices_Hi
:= Table
(Nb_Choices
).Choice_Hi
;
3745 end Compute_Choices_Lo_And_Choices_Hi
;
3748 -- If no others choice in this sub-aggregate, or the aggregate
3749 -- comprises only an others choice, nothing to do.
3751 if not Need_To_Check
then
3754 -- If we are dealing with an aggregate containing an others
3755 -- choice and positional components, we generate the following test:
3757 -- if Ind_Typ'Pos (Aggr_Lo) + (Nb_Elements - 1) >
3758 -- Ind_Typ'Pos (Aggr_Hi)
3760 -- raise Constraint_Error;
3763 elsif Nb_Elements
> Uint_0
then
3769 Make_Attribute_Reference
(Loc
,
3770 Prefix
=> New_Reference_To
(Ind_Typ
, Loc
),
3771 Attribute_Name
=> Name_Pos
,
3774 (Duplicate_Subexpr_Move_Checks
(Aggr_Lo
))),
3775 Right_Opnd
=> Make_Integer_Literal
(Loc
, Nb_Elements
- 1)),
3778 Make_Attribute_Reference
(Loc
,
3779 Prefix
=> New_Reference_To
(Ind_Typ
, Loc
),
3780 Attribute_Name
=> Name_Pos
,
3781 Expressions
=> New_List
(
3782 Duplicate_Subexpr_Move_Checks
(Aggr_Hi
))));
3784 -- If we are dealing with an aggregate containing an others
3785 -- choice and discrete choices we generate the following test:
3787 -- [constraint_error when
3788 -- Choices_Lo < Aggr_Lo or else Choices_Hi > Aggr_Hi];
3796 Duplicate_Subexpr_Move_Checks
(Choices_Lo
),
3798 Duplicate_Subexpr_Move_Checks
(Aggr_Lo
)),
3803 Duplicate_Subexpr
(Choices_Hi
),
3805 Duplicate_Subexpr
(Aggr_Hi
)));
3808 if Present
(Cond
) then
3810 Make_Raise_Constraint_Error
(Loc
,
3812 Reason
=> CE_Length_Check_Failed
));
3815 -- Now look inside the sub-aggregate to see if there is more work
3817 if Dim
< Aggr_Dimension
then
3819 -- Process positional components
3821 if Present
(Expressions
(Sub_Aggr
)) then
3822 Expr
:= First
(Expressions
(Sub_Aggr
));
3823 while Present
(Expr
) loop
3824 Others_Check
(Expr
, Dim
+ 1);
3829 -- Process component associations
3831 if Present
(Component_Associations
(Sub_Aggr
)) then
3832 Assoc
:= First
(Component_Associations
(Sub_Aggr
));
3833 while Present
(Assoc
) loop
3834 Expr
:= Expression
(Assoc
);
3835 Others_Check
(Expr
, Dim
+ 1);
3842 -- Remaining Expand_Array_Aggregate variables
3845 -- Holds the temporary aggregate value
3848 -- Holds the declaration of Tmp
3850 Aggr_Code
: List_Id
;
3851 Parent_Node
: Node_Id
;
3852 Parent_Kind
: Node_Kind
;
3854 -- Start of processing for Expand_Array_Aggregate
3857 -- Do not touch the special aggregates of attributes used for Asm calls
3859 if Is_RTE
(Ctyp
, RE_Asm_Input_Operand
)
3860 or else Is_RTE
(Ctyp
, RE_Asm_Output_Operand
)
3865 -- If the semantic analyzer has determined that aggregate N will raise
3866 -- Constraint_Error at run-time, then the aggregate node has been
3867 -- replaced with an N_Raise_Constraint_Error node and we should
3870 pragma Assert
(not Raises_Constraint_Error
(N
));
3874 -- Check that the index range defined by aggregate bounds is
3875 -- compatible with corresponding index subtype.
3877 Index_Compatibility_Check
: declare
3878 Aggr_Index_Range
: Node_Id
:= First_Index
(Typ
);
3879 -- The current aggregate index range
3881 Index_Constraint
: Node_Id
:= First_Index
(Etype
(Typ
));
3882 -- The corresponding index constraint against which we have to
3883 -- check the above aggregate index range.
3886 Compute_Others_Present
(N
, 1);
3888 for J
in 1 .. Aggr_Dimension
loop
3889 -- There is no need to emit a check if an others choice is
3890 -- present for this array aggregate dimension since in this
3891 -- case one of N's sub-aggregates has taken its bounds from the
3892 -- context and these bounds must have been checked already. In
3893 -- addition all sub-aggregates corresponding to the same
3894 -- dimension must all have the same bounds (checked in (c) below).
3896 if not Range_Checks_Suppressed
(Etype
(Index_Constraint
))
3897 and then not Others_Present
(J
)
3899 -- We don't use Checks.Apply_Range_Check here because it
3900 -- emits a spurious check. Namely it checks that the range
3901 -- defined by the aggregate bounds is non empty. But we know
3902 -- this already if we get here.
3904 Check_Bounds
(Aggr_Index_Range
, Index_Constraint
);
3907 -- Save the low and high bounds of the aggregate index as well
3908 -- as the index type for later use in checks (b) and (c) below.
3910 Aggr_Low
(J
) := Low_Bound
(Aggr_Index_Range
);
3911 Aggr_High
(J
) := High_Bound
(Aggr_Index_Range
);
3913 Aggr_Index_Typ
(J
) := Etype
(Index_Constraint
);
3915 Next_Index
(Aggr_Index_Range
);
3916 Next_Index
(Index_Constraint
);
3918 end Index_Compatibility_Check
;
3922 -- If an others choice is present check that no aggregate
3923 -- index is outside the bounds of the index constraint.
3925 Others_Check
(N
, 1);
3929 -- For multidimensional arrays make sure that all subaggregates
3930 -- corresponding to the same dimension have the same bounds.
3932 if Aggr_Dimension
> 1 then
3933 Check_Same_Aggr_Bounds
(N
, 1);
3938 -- Here we test for is packed array aggregate that we can handle
3939 -- at compile time. If so, return with transformation done. Note
3940 -- that we do this even if the aggregate is nested, because once
3941 -- we have done this processing, there is no more nested aggregate!
3943 if Packed_Array_Aggregate_Handled
(N
) then
3947 -- At this point we try to convert to positional form
3949 Convert_To_Positional
(N
);
3951 -- if the result is no longer an aggregate (e.g. it may be a string
3952 -- literal, or a temporary which has the needed value), then we are
3953 -- done, since there is no longer a nested aggregate.
3955 if Nkind
(N
) /= N_Aggregate
then
3958 -- We are also done if the result is an analyzed aggregate
3959 -- This case could use more comments ???
3962 and then N
/= Original_Node
(N
)
3967 -- Now see if back end processing is possible
3969 if Backend_Processing_Possible
(N
) then
3971 -- If the aggregate is static but the constraints are not, build
3972 -- a static subtype for the aggregate, so that Gigi can place it
3973 -- in static memory. Perform an unchecked_conversion to the non-
3974 -- static type imposed by the context.
3977 Itype
: constant Entity_Id
:= Etype
(N
);
3979 Needs_Type
: Boolean := False;
3982 Index
:= First_Index
(Itype
);
3984 while Present
(Index
) loop
3985 if not Is_Static_Subtype
(Etype
(Index
)) then
3994 Build_Constrained_Type
(Positional
=> True);
3995 Rewrite
(N
, Unchecked_Convert_To
(Itype
, N
));
4005 -- Delay expansion for nested aggregates it will be taken care of
4006 -- when the parent aggregate is expanded
4008 Parent_Node
:= Parent
(N
);
4009 Parent_Kind
:= Nkind
(Parent_Node
);
4011 if Parent_Kind
= N_Qualified_Expression
then
4012 Parent_Node
:= Parent
(Parent_Node
);
4013 Parent_Kind
:= Nkind
(Parent_Node
);
4016 if Parent_Kind
= N_Aggregate
4017 or else Parent_Kind
= N_Extension_Aggregate
4018 or else Parent_Kind
= N_Component_Association
4019 or else (Parent_Kind
= N_Object_Declaration
4020 and then Controlled_Type
(Typ
))
4021 or else (Parent_Kind
= N_Assignment_Statement
4022 and then Inside_Init_Proc
)
4024 Set_Expansion_Delayed
(N
);
4030 -- Look if in place aggregate expansion is possible
4032 -- For object declarations we build the aggregate in place, unless
4033 -- the array is bit-packed or the component is controlled.
4035 -- For assignments we do the assignment in place if all the component
4036 -- associations have compile-time known values. For other cases we
4037 -- create a temporary. The analysis for safety of on-line assignment
4038 -- is delicate, i.e. we don't know how to do it fully yet ???
4040 -- For allocators we assign to the designated object in place if the
4041 -- aggregate meets the same conditions as other in-place assignments.
4042 -- In this case the aggregate may not come from source but was created
4043 -- for default initialization, e.g. with Initialize_Scalars.
4045 if Requires_Transient_Scope
(Typ
) then
4046 Establish_Transient_Scope
4047 (N
, Sec_Stack
=> Has_Controlled_Component
(Typ
));
4050 if Has_Default_Init_Comps
(N
) then
4051 Maybe_In_Place_OK
:= False;
4053 elsif Is_Bit_Packed_Array
(Typ
)
4054 or else Has_Controlled_Component
(Typ
)
4056 Maybe_In_Place_OK
:= False;
4059 Maybe_In_Place_OK
:=
4060 (Nkind
(Parent
(N
)) = N_Assignment_Statement
4061 and then Comes_From_Source
(N
)
4062 and then In_Place_Assign_OK
)
4065 (Nkind
(Parent
(Parent
(N
))) = N_Allocator
4066 and then In_Place_Assign_OK
);
4069 if not Has_Default_Init_Comps
(N
)
4070 and then Comes_From_Source
(Parent
(N
))
4071 and then Nkind
(Parent
(N
)) = N_Object_Declaration
4073 Must_Slide
(Etype
(Defining_Identifier
(Parent
(N
))), Typ
)
4074 and then N
= Expression
(Parent
(N
))
4075 and then not Is_Bit_Packed_Array
(Typ
)
4076 and then not Has_Controlled_Component
(Typ
)
4077 and then not Has_Address_Clause
(Parent
(N
))
4079 Tmp
:= Defining_Identifier
(Parent
(N
));
4080 Set_No_Initialization
(Parent
(N
));
4081 Set_Expression
(Parent
(N
), Empty
);
4083 -- Set the type of the entity, for use in the analysis of the
4084 -- subsequent indexed assignments. If the nominal type is not
4085 -- constrained, build a subtype from the known bounds of the
4086 -- aggregate. If the declaration has a subtype mark, use it,
4087 -- otherwise use the itype of the aggregate.
4089 if not Is_Constrained
(Typ
) then
4090 Build_Constrained_Type
(Positional
=> False);
4091 elsif Is_Entity_Name
(Object_Definition
(Parent
(N
)))
4092 and then Is_Constrained
(Entity
(Object_Definition
(Parent
(N
))))
4094 Set_Etype
(Tmp
, Entity
(Object_Definition
(Parent
(N
))));
4096 Set_Size_Known_At_Compile_Time
(Typ
, False);
4097 Set_Etype
(Tmp
, Typ
);
4100 elsif Maybe_In_Place_OK
4101 and then Nkind
(Parent
(N
)) = N_Qualified_Expression
4102 and then Nkind
(Parent
(Parent
(N
))) = N_Allocator
4104 Set_Expansion_Delayed
(N
);
4107 -- In the remaining cases the aggregate is the RHS of an assignment
4109 elsif Maybe_In_Place_OK
4110 and then Is_Entity_Name
(Name
(Parent
(N
)))
4112 Tmp
:= Entity
(Name
(Parent
(N
)));
4114 if Etype
(Tmp
) /= Etype
(N
) then
4115 Apply_Length_Check
(N
, Etype
(Tmp
));
4117 if Nkind
(N
) = N_Raise_Constraint_Error
then
4119 -- Static error, nothing further to expand
4125 elsif Maybe_In_Place_OK
4126 and then Nkind
(Name
(Parent
(N
))) = N_Explicit_Dereference
4127 and then Is_Entity_Name
(Prefix
(Name
(Parent
(N
))))
4129 Tmp
:= Name
(Parent
(N
));
4131 if Etype
(Tmp
) /= Etype
(N
) then
4132 Apply_Length_Check
(N
, Etype
(Tmp
));
4135 elsif Maybe_In_Place_OK
4136 and then Nkind
(Name
(Parent
(N
))) = N_Slice
4137 and then Safe_Slice_Assignment
(N
)
4139 -- Safe_Slice_Assignment rewrites assignment as a loop
4145 -- In place aggregate expansion is not possible
4148 Maybe_In_Place_OK
:= False;
4149 Tmp
:= Make_Defining_Identifier
(Loc
, New_Internal_Name
('A'));
4151 Make_Object_Declaration
4153 Defining_Identifier
=> Tmp
,
4154 Object_Definition
=> New_Occurrence_Of
(Typ
, Loc
));
4155 Set_No_Initialization
(Tmp_Decl
, True);
4157 -- If we are within a loop, the temporary will be pushed on the
4158 -- stack at each iteration. If the aggregate is the expression for
4159 -- an allocator, it will be immediately copied to the heap and can
4160 -- be reclaimed at once. We create a transient scope around the
4161 -- aggregate for this purpose.
4163 if Ekind
(Current_Scope
) = E_Loop
4164 and then Nkind
(Parent
(Parent
(N
))) = N_Allocator
4166 Establish_Transient_Scope
(N
, False);
4169 Insert_Action
(N
, Tmp_Decl
);
4172 -- Construct and insert the aggregate code. We can safely suppress
4173 -- index checks because this code is guaranteed not to raise CE
4174 -- on index checks. However we should *not* suppress all checks.
4180 if Nkind
(Tmp
) = N_Defining_Identifier
then
4181 Target
:= New_Reference_To
(Tmp
, Loc
);
4185 if Has_Default_Init_Comps
(N
) then
4187 -- Ada 2005 (AI-287): This case has not been analyzed???
4189 raise Program_Error
;
4192 -- Name in assignment is explicit dereference
4194 Target
:= New_Copy
(Tmp
);
4198 Build_Array_Aggr_Code
(N
,
4200 Index
=> First_Index
(Typ
),
4202 Scalar_Comp
=> Is_Scalar_Type
(Ctyp
));
4205 if Comes_From_Source
(Tmp
) then
4206 Insert_Actions_After
(Parent
(N
), Aggr_Code
);
4209 Insert_Actions
(N
, Aggr_Code
);
4212 -- If the aggregate has been assigned in place, remove the original
4215 if Nkind
(Parent
(N
)) = N_Assignment_Statement
4216 and then Maybe_In_Place_OK
4218 Rewrite
(Parent
(N
), Make_Null_Statement
(Loc
));
4220 elsif Nkind
(Parent
(N
)) /= N_Object_Declaration
4221 or else Tmp
/= Defining_Identifier
(Parent
(N
))
4223 Rewrite
(N
, New_Occurrence_Of
(Tmp
, Loc
));
4224 Analyze_And_Resolve
(N
, Typ
);
4226 end Expand_Array_Aggregate
;
4228 ------------------------
4229 -- Expand_N_Aggregate --
4230 ------------------------
4232 procedure Expand_N_Aggregate
(N
: Node_Id
) is
4234 if Is_Record_Type
(Etype
(N
)) then
4235 Expand_Record_Aggregate
(N
);
4237 Expand_Array_Aggregate
(N
);
4241 when RE_Not_Available
=>
4243 end Expand_N_Aggregate
;
4245 ----------------------------------
4246 -- Expand_N_Extension_Aggregate --
4247 ----------------------------------
4249 -- If the ancestor part is an expression, add a component association for
4250 -- the parent field. If the type of the ancestor part is not the direct
4251 -- parent of the expected type, build recursively the needed ancestors.
4252 -- If the ancestor part is a subtype_mark, replace aggregate with a decla-
4253 -- ration for a temporary of the expected type, followed by individual
4254 -- assignments to the given components.
4256 procedure Expand_N_Extension_Aggregate
(N
: Node_Id
) is
4257 Loc
: constant Source_Ptr
:= Sloc
(N
);
4258 A
: constant Node_Id
:= Ancestor_Part
(N
);
4259 Typ
: constant Entity_Id
:= Etype
(N
);
4262 -- If the ancestor is a subtype mark, an init proc must be called
4263 -- on the resulting object which thus has to be materialized in
4266 if Is_Entity_Name
(A
) and then Is_Type
(Entity
(A
)) then
4267 Convert_To_Assignments
(N
, Typ
);
4269 -- The extension aggregate is transformed into a record aggregate
4270 -- of the following form (c1 and c2 are inherited components)
4272 -- (Exp with c3 => a, c4 => b)
4273 -- ==> (c1 => Exp.c1, c2 => Exp.c2, c1 => a, c2 => b)
4278 -- No tag is needed in the case of Java_VM
4281 Expand_Record_Aggregate
(N
,
4284 Expand_Record_Aggregate
(N
,
4285 Orig_Tag
=> New_Occurrence_Of
(Access_Disp_Table
(Typ
), Loc
),
4291 when RE_Not_Available
=>
4293 end Expand_N_Extension_Aggregate
;
4295 -----------------------------
4296 -- Expand_Record_Aggregate --
4297 -----------------------------
4299 procedure Expand_Record_Aggregate
4301 Orig_Tag
: Node_Id
:= Empty
;
4302 Parent_Expr
: Node_Id
:= Empty
)
4304 Loc
: constant Source_Ptr
:= Sloc
(N
);
4305 Comps
: constant List_Id
:= Component_Associations
(N
);
4306 Typ
: constant Entity_Id
:= Etype
(N
);
4307 Base_Typ
: constant Entity_Id
:= Base_Type
(Typ
);
4309 function Has_Delayed_Nested_Aggregate_Or_Tagged_Comps
return Boolean;
4310 -- Checks the presence of a nested aggregate which needs Late_Expansion
4311 -- or the presence of tagged components which may need tag adjustment.
4313 --------------------------------------------------
4314 -- Has_Delayed_Nested_Aggregate_Or_Tagged_Comps --
4315 --------------------------------------------------
4317 function Has_Delayed_Nested_Aggregate_Or_Tagged_Comps
return Boolean is
4327 while Present
(C
) loop
4328 if Nkind
(Expression
(C
)) = N_Qualified_Expression
then
4329 Expr_Q
:= Expression
(Expression
(C
));
4331 Expr_Q
:= Expression
(C
);
4334 -- Return true if the aggregate has any associations for
4335 -- tagged components that may require tag adjustment.
4336 -- These are cases where the source expression may have
4337 -- a tag that could differ from the component tag (e.g.,
4338 -- can occur for type conversions and formal parameters).
4339 -- (Tag adjustment is not needed if Java_VM because object
4340 -- tags are implicit in the JVM.)
4342 if Is_Tagged_Type
(Etype
(Expr_Q
))
4343 and then (Nkind
(Expr_Q
) = N_Type_Conversion
4344 or else (Is_Entity_Name
(Expr_Q
)
4345 and then Ekind
(Entity
(Expr_Q
)) in Formal_Kind
))
4346 and then not Java_VM
4351 if Is_Delayed_Aggregate
(Expr_Q
) then
4359 end Has_Delayed_Nested_Aggregate_Or_Tagged_Comps
;
4361 -- Remaining Expand_Record_Aggregate variables
4363 Tag_Value
: Node_Id
;
4367 -- Start of processing for Expand_Record_Aggregate
4370 -- If the aggregate is to be assigned to an atomic variable, we
4371 -- have to prevent a piecemeal assignment even if the aggregate
4372 -- is to be expanded. We create a temporary for the aggregate, and
4373 -- assign the temporary instead, so that the back end can generate
4374 -- an atomic move for it.
4377 and then (Nkind
(Parent
(N
)) = N_Object_Declaration
4378 or else Nkind
(Parent
(N
)) = N_Assignment_Statement
)
4379 and then Comes_From_Source
(Parent
(N
))
4381 Expand_Atomic_Aggregate
(N
, Typ
);
4385 -- Gigi doesn't handle properly temporaries of variable size
4386 -- so we generate it in the front-end
4388 if not Size_Known_At_Compile_Time
(Typ
) then
4389 Convert_To_Assignments
(N
, Typ
);
4391 -- Temporaries for controlled aggregates need to be attached to a
4392 -- final chain in order to be properly finalized, so it has to
4393 -- be created in the front-end
4395 elsif Is_Controlled
(Typ
)
4396 or else Has_Controlled_Component
(Base_Type
(Typ
))
4398 Convert_To_Assignments
(N
, Typ
);
4400 -- Ada 2005 (AI-287): In case of default initialized components we
4401 -- convert the aggregate into assignments.
4403 elsif Has_Default_Init_Comps
(N
) then
4404 Convert_To_Assignments
(N
, Typ
);
4406 elsif Has_Delayed_Nested_Aggregate_Or_Tagged_Comps
then
4407 Convert_To_Assignments
(N
, Typ
);
4409 -- If an ancestor is private, some components are not inherited and
4410 -- we cannot expand into a record aggregate
4412 elsif Has_Private_Ancestor
(Typ
) then
4413 Convert_To_Assignments
(N
, Typ
);
4415 -- ??? The following was done to compile fxacc00.ads in the ACVCs. Gigi
4416 -- is not able to handle the aggregate for Late_Request.
4418 elsif Is_Tagged_Type
(Typ
) and then Has_Discriminants
(Typ
) then
4419 Convert_To_Assignments
(N
, Typ
);
4421 -- If some components are mutable, the size of the aggregate component
4422 -- may be disctinct from the default size of the type component, so
4423 -- we need to expand to insure that the back-end copies the proper
4424 -- size of the data.
4426 elsif Has_Mutable_Components
(Typ
) then
4427 Convert_To_Assignments
(N
, Typ
);
4429 -- If the type involved has any non-bit aligned components, then
4430 -- we are not sure that the back end can handle this case correctly.
4432 elsif Type_May_Have_Bit_Aligned_Components
(Typ
) then
4433 Convert_To_Assignments
(N
, Typ
);
4435 -- In all other cases we generate a proper aggregate that
4436 -- can be handled by gigi.
4439 -- If no discriminants, nothing special to do
4441 if not Has_Discriminants
(Typ
) then
4444 -- Case of discriminants present
4446 elsif Is_Derived_Type
(Typ
) then
4448 -- For untagged types, non-stored discriminants are replaced
4449 -- with stored discriminants, which are the ones that gigi uses
4450 -- to describe the type and its components.
4452 Generate_Aggregate_For_Derived_Type
: declare
4453 Constraints
: constant List_Id
:= New_List
;
4454 First_Comp
: Node_Id
;
4455 Discriminant
: Entity_Id
;
4457 Num_Disc
: Int
:= 0;
4458 Num_Gird
: Int
:= 0;
4460 procedure Prepend_Stored_Values
(T
: Entity_Id
);
4461 -- Scan the list of stored discriminants of the type, and
4462 -- add their values to the aggregate being built.
4464 ---------------------------
4465 -- Prepend_Stored_Values --
4466 ---------------------------
4468 procedure Prepend_Stored_Values
(T
: Entity_Id
) is
4470 Discriminant
:= First_Stored_Discriminant
(T
);
4472 while Present
(Discriminant
) loop
4474 Make_Component_Association
(Loc
,
4476 New_List
(New_Occurrence_Of
(Discriminant
, Loc
)),
4480 Get_Discriminant_Value
(
4483 Discriminant_Constraint
(Typ
))));
4485 if No
(First_Comp
) then
4486 Prepend_To
(Component_Associations
(N
), New_Comp
);
4488 Insert_After
(First_Comp
, New_Comp
);
4491 First_Comp
:= New_Comp
;
4492 Next_Stored_Discriminant
(Discriminant
);
4494 end Prepend_Stored_Values
;
4496 -- Start of processing for Generate_Aggregate_For_Derived_Type
4499 -- Remove the associations for the discriminant of
4500 -- the derived type.
4502 First_Comp
:= First
(Component_Associations
(N
));
4504 while Present
(First_Comp
) loop
4508 if Ekind
(Entity
(First
(Choices
(Comp
)))) =
4512 Num_Disc
:= Num_Disc
+ 1;
4516 -- Insert stored discriminant associations in the correct
4517 -- order. If there are more stored discriminants than new
4518 -- discriminants, there is at least one new discriminant
4519 -- that constrains more than one of the stored discriminants.
4520 -- In this case we need to construct a proper subtype of
4521 -- the parent type, in order to supply values to all the
4522 -- components. Otherwise there is one-one correspondence
4523 -- between the constraints and the stored discriminants.
4525 First_Comp
:= Empty
;
4527 Discriminant
:= First_Stored_Discriminant
(Base_Type
(Typ
));
4529 while Present
(Discriminant
) loop
4530 Num_Gird
:= Num_Gird
+ 1;
4531 Next_Stored_Discriminant
(Discriminant
);
4534 -- Case of more stored discriminants than new discriminants
4536 if Num_Gird
> Num_Disc
then
4538 -- Create a proper subtype of the parent type, which is
4539 -- the proper implementation type for the aggregate, and
4540 -- convert it to the intended target type.
4542 Discriminant
:= First_Stored_Discriminant
(Base_Type
(Typ
));
4544 while Present
(Discriminant
) loop
4547 Get_Discriminant_Value
(
4550 Discriminant_Constraint
(Typ
)));
4551 Append
(New_Comp
, Constraints
);
4552 Next_Stored_Discriminant
(Discriminant
);
4556 Make_Subtype_Declaration
(Loc
,
4557 Defining_Identifier
=>
4558 Make_Defining_Identifier
(Loc
,
4559 New_Internal_Name
('T')),
4560 Subtype_Indication
=>
4561 Make_Subtype_Indication
(Loc
,
4563 New_Occurrence_Of
(Etype
(Base_Type
(Typ
)), Loc
),
4565 Make_Index_Or_Discriminant_Constraint
4566 (Loc
, Constraints
)));
4568 Insert_Action
(N
, Decl
);
4569 Prepend_Stored_Values
(Base_Type
(Typ
));
4571 Set_Etype
(N
, Defining_Identifier
(Decl
));
4574 Rewrite
(N
, Unchecked_Convert_To
(Typ
, N
));
4577 -- Case where we do not have fewer new discriminants than
4578 -- stored discriminants, so in this case we can simply
4579 -- use the stored discriminants of the subtype.
4582 Prepend_Stored_Values
(Typ
);
4584 end Generate_Aggregate_For_Derived_Type
;
4587 if Is_Tagged_Type
(Typ
) then
4589 -- The tagged case, _parent and _tag component must be created
4591 -- Reset null_present unconditionally. tagged records always have
4592 -- at least one field (the tag or the parent)
4594 Set_Null_Record_Present
(N
, False);
4596 -- When the current aggregate comes from the expansion of an
4597 -- extension aggregate, the parent expr is replaced by an
4598 -- aggregate formed by selected components of this expr
4600 if Present
(Parent_Expr
)
4601 and then Is_Empty_List
(Comps
)
4603 Comp
:= First_Entity
(Typ
);
4604 while Present
(Comp
) loop
4606 -- Skip all entities that aren't discriminants or components
4608 if Ekind
(Comp
) /= E_Discriminant
4609 and then Ekind
(Comp
) /= E_Component
4613 -- Skip all expander-generated components
4616 not Comes_From_Source
(Original_Record_Component
(Comp
))
4622 Make_Selected_Component
(Loc
,
4624 Unchecked_Convert_To
(Typ
,
4625 Duplicate_Subexpr
(Parent_Expr
, True)),
4627 Selector_Name
=> New_Occurrence_Of
(Comp
, Loc
));
4630 Make_Component_Association
(Loc
,
4632 New_List
(New_Occurrence_Of
(Comp
, Loc
)),
4636 Analyze_And_Resolve
(New_Comp
, Etype
(Comp
));
4643 -- Compute the value for the Tag now, if the type is a root it
4644 -- will be included in the aggregate right away, otherwise it will
4645 -- be propagated to the parent aggregate
4647 if Present
(Orig_Tag
) then
4648 Tag_Value
:= Orig_Tag
;
4652 Tag_Value
:= New_Occurrence_Of
(Access_Disp_Table
(Typ
), Loc
);
4655 -- For a derived type, an aggregate for the parent is formed with
4656 -- all the inherited components.
4658 if Is_Derived_Type
(Typ
) then
4661 First_Comp
: Node_Id
;
4662 Parent_Comps
: List_Id
;
4663 Parent_Aggr
: Node_Id
;
4664 Parent_Name
: Node_Id
;
4667 -- Remove the inherited component association from the
4668 -- aggregate and store them in the parent aggregate
4670 First_Comp
:= First
(Component_Associations
(N
));
4671 Parent_Comps
:= New_List
;
4673 while Present
(First_Comp
)
4674 and then Scope
(Original_Record_Component
(
4675 Entity
(First
(Choices
(First_Comp
))))) /= Base_Typ
4680 Append
(Comp
, Parent_Comps
);
4683 Parent_Aggr
:= Make_Aggregate
(Loc
,
4684 Component_Associations
=> Parent_Comps
);
4685 Set_Etype
(Parent_Aggr
, Etype
(Base_Type
(Typ
)));
4687 -- Find the _parent component
4689 Comp
:= First_Component
(Typ
);
4690 while Chars
(Comp
) /= Name_uParent
loop
4691 Comp
:= Next_Component
(Comp
);
4694 Parent_Name
:= New_Occurrence_Of
(Comp
, Loc
);
4696 -- Insert the parent aggregate
4698 Prepend_To
(Component_Associations
(N
),
4699 Make_Component_Association
(Loc
,
4700 Choices
=> New_List
(Parent_Name
),
4701 Expression
=> Parent_Aggr
));
4703 -- Expand recursively the parent propagating the right Tag
4705 Expand_Record_Aggregate
(
4706 Parent_Aggr
, Tag_Value
, Parent_Expr
);
4709 -- For a root type, the tag component is added (unless compiling
4710 -- for the Java VM, where tags are implicit).
4712 elsif not Java_VM
then
4714 Tag_Name
: constant Node_Id
:=
4715 New_Occurrence_Of
(Tag_Component
(Typ
), Loc
);
4716 Typ_Tag
: constant Entity_Id
:= RTE
(RE_Tag
);
4717 Conv_Node
: constant Node_Id
:=
4718 Unchecked_Convert_To
(Typ_Tag
, Tag_Value
);
4721 Set_Etype
(Conv_Node
, Typ_Tag
);
4722 Prepend_To
(Component_Associations
(N
),
4723 Make_Component_Association
(Loc
,
4724 Choices
=> New_List
(Tag_Name
),
4725 Expression
=> Conv_Node
));
4730 end Expand_Record_Aggregate
;
4732 ----------------------------
4733 -- Has_Default_Init_Comps --
4734 ----------------------------
4736 function Has_Default_Init_Comps
(N
: Node_Id
) return Boolean is
4737 Comps
: constant List_Id
:= Component_Associations
(N
);
4741 pragma Assert
(Nkind
(N
) = N_Aggregate
4742 or else Nkind
(N
) = N_Extension_Aggregate
);
4748 -- Check if any direct component has default initialized components
4751 while Present
(C
) loop
4752 if Box_Present
(C
) then
4759 -- Recursive call in case of aggregate expression
4762 while Present
(C
) loop
4763 Expr
:= Expression
(C
);
4766 and then (Nkind
(Expr
) = N_Aggregate
4767 or else Nkind
(Expr
) = N_Extension_Aggregate
)
4768 and then Has_Default_Init_Comps
(Expr
)
4777 end Has_Default_Init_Comps
;
4779 --------------------------
4780 -- Is_Delayed_Aggregate --
4781 --------------------------
4783 function Is_Delayed_Aggregate
(N
: Node_Id
) return Boolean is
4784 Node
: Node_Id
:= N
;
4785 Kind
: Node_Kind
:= Nkind
(Node
);
4788 if Kind
= N_Qualified_Expression
then
4789 Node
:= Expression
(Node
);
4790 Kind
:= Nkind
(Node
);
4793 if Kind
/= N_Aggregate
and then Kind
/= N_Extension_Aggregate
then
4796 return Expansion_Delayed
(Node
);
4798 end Is_Delayed_Aggregate
;
4800 --------------------
4801 -- Late_Expansion --
4802 --------------------
4804 function Late_Expansion
4808 Flist
: Node_Id
:= Empty
;
4809 Obj
: Entity_Id
:= Empty
) return List_Id
4812 if Is_Record_Type
(Etype
(N
)) then
4813 return Build_Record_Aggr_Code
(N
, Typ
, Target
, Flist
, Obj
);
4815 else pragma Assert
(Is_Array_Type
(Etype
(N
)));
4817 Build_Array_Aggr_Code
4819 Ctype
=> Component_Type
(Etype
(N
)),
4820 Index
=> First_Index
(Typ
),
4822 Scalar_Comp
=> Is_Scalar_Type
(Component_Type
(Typ
)),
4828 ----------------------------------
4829 -- Make_OK_Assignment_Statement --
4830 ----------------------------------
4832 function Make_OK_Assignment_Statement
4835 Expression
: Node_Id
) return Node_Id
4838 Set_Assignment_OK
(Name
);
4839 return Make_Assignment_Statement
(Sloc
, Name
, Expression
);
4840 end Make_OK_Assignment_Statement
;
4842 -----------------------
4843 -- Number_Of_Choices --
4844 -----------------------
4846 function Number_Of_Choices
(N
: Node_Id
) return Nat
is
4850 Nb_Choices
: Nat
:= 0;
4853 if Present
(Expressions
(N
)) then
4857 Assoc
:= First
(Component_Associations
(N
));
4858 while Present
(Assoc
) loop
4860 Choice
:= First
(Choices
(Assoc
));
4861 while Present
(Choice
) loop
4863 if Nkind
(Choice
) /= N_Others_Choice
then
4864 Nb_Choices
:= Nb_Choices
+ 1;
4874 end Number_Of_Choices
;
4876 ------------------------------------
4877 -- Packed_Array_Aggregate_Handled --
4878 ------------------------------------
4880 -- The current version of this procedure will handle at compile time
4881 -- any array aggregate that meets these conditions:
4883 -- One dimensional, bit packed
4884 -- Underlying packed type is modular type
4885 -- Bounds are within 32-bit Int range
4886 -- All bounds and values are static
4888 function Packed_Array_Aggregate_Handled
(N
: Node_Id
) return Boolean is
4889 Loc
: constant Source_Ptr
:= Sloc
(N
);
4890 Typ
: constant Entity_Id
:= Etype
(N
);
4891 Ctyp
: constant Entity_Id
:= Component_Type
(Typ
);
4893 Not_Handled
: exception;
4894 -- Exception raised if this aggregate cannot be handled
4897 -- For now, handle only one dimensional bit packed arrays
4899 if not Is_Bit_Packed_Array
(Typ
)
4900 or else Number_Dimensions
(Typ
) > 1
4901 or else not Is_Modular_Integer_Type
(Packed_Array_Type
(Typ
))
4907 Csiz
: constant Nat
:= UI_To_Int
(Component_Size
(Typ
));
4911 -- Bounds of index type
4915 -- Values of bounds if compile time known
4917 function Get_Component_Val
(N
: Node_Id
) return Uint
;
4918 -- Given a expression value N of the component type Ctyp, returns
4919 -- A value of Csiz (component size) bits representing this value.
4920 -- If the value is non-static or any other reason exists why the
4921 -- value cannot be returned, then Not_Handled is raised.
4923 -----------------------
4924 -- Get_Component_Val --
4925 -----------------------
4927 function Get_Component_Val
(N
: Node_Id
) return Uint
is
4931 -- We have to analyze the expression here before doing any further
4932 -- processing here. The analysis of such expressions is deferred
4933 -- till expansion to prevent some problems of premature analysis.
4935 Analyze_And_Resolve
(N
, Ctyp
);
4937 -- Must have a compile time value. String literals have to
4938 -- be converted into temporaries as well, because they cannot
4939 -- easily be converted into their bit representation.
4941 if not Compile_Time_Known_Value
(N
)
4942 or else Nkind
(N
) = N_String_Literal
4947 Val
:= Expr_Rep_Value
(N
);
4949 -- Adjust for bias, and strip proper number of bits
4951 if Has_Biased_Representation
(Ctyp
) then
4952 Val
:= Val
- Expr_Value
(Type_Low_Bound
(Ctyp
));
4955 return Val
mod Uint_2
** Csiz
;
4956 end Get_Component_Val
;
4958 -- Here we know we have a one dimensional bit packed array
4961 Get_Index_Bounds
(First_Index
(Typ
), Lo
, Hi
);
4963 -- Cannot do anything if bounds are dynamic
4965 if not Compile_Time_Known_Value
(Lo
)
4967 not Compile_Time_Known_Value
(Hi
)
4972 -- Or are silly out of range of int bounds
4974 Lob
:= Expr_Value
(Lo
);
4975 Hib
:= Expr_Value
(Hi
);
4977 if not UI_Is_In_Int_Range
(Lob
)
4979 not UI_Is_In_Int_Range
(Hib
)
4984 -- At this stage we have a suitable aggregate for handling
4985 -- at compile time (the only remaining checks, are that the
4986 -- values of expressions in the aggregate are compile time
4987 -- known (check performed by Get_Component_Val), and that
4988 -- any subtypes or ranges are statically known.
4990 -- If the aggregate is not fully positional at this stage,
4991 -- then convert it to positional form. Either this will fail,
4992 -- in which case we can do nothing, or it will succeed, in
4993 -- which case we have succeeded in handling the aggregate,
4994 -- or it will stay an aggregate, in which case we have failed
4995 -- to handle this case.
4997 if Present
(Component_Associations
(N
)) then
4998 Convert_To_Positional
4999 (N
, Max_Others_Replicate
=> 64, Handle_Bit_Packed
=> True);
5000 return Nkind
(N
) /= N_Aggregate
;
5003 -- Otherwise we are all positional, so convert to proper value
5006 Lov
: constant Int
:= UI_To_Int
(Lob
);
5007 Hiv
: constant Int
:= UI_To_Int
(Hib
);
5009 Len
: constant Nat
:= Int
'Max (0, Hiv
- Lov
+ 1);
5010 -- The length of the array (number of elements)
5012 Aggregate_Val
: Uint
;
5013 -- Value of aggregate. The value is set in the low order
5014 -- bits of this value. For the little-endian case, the
5015 -- values are stored from low-order to high-order and
5016 -- for the big-endian case the values are stored from
5017 -- high-order to low-order. Note that gigi will take care
5018 -- of the conversions to left justify the value in the big
5019 -- endian case (because of left justified modular type
5020 -- processing), so we do not have to worry about that here.
5023 -- Integer literal for resulting constructed value
5026 -- Shift count from low order for next value
5029 -- Shift increment for loop
5032 -- Next expression from positional parameters of aggregate
5035 -- For little endian, we fill up the low order bits of the
5036 -- target value. For big endian we fill up the high order
5037 -- bits of the target value (which is a left justified
5040 if Bytes_Big_Endian
xor Debug_Flag_8
then
5041 Shift
:= Csiz
* (Len
- 1);
5048 -- Loop to set the values
5051 Aggregate_Val
:= Uint_0
;
5053 Expr
:= First
(Expressions
(N
));
5054 Aggregate_Val
:= Get_Component_Val
(Expr
) * Uint_2
** Shift
;
5056 for J
in 2 .. Len
loop
5057 Shift
:= Shift
+ Incr
;
5060 Aggregate_Val
+ Get_Component_Val
(Expr
) * Uint_2
** Shift
;
5064 -- Now we can rewrite with the proper value
5067 Make_Integer_Literal
(Loc
,
5068 Intval
=> Aggregate_Val
);
5069 Set_Print_In_Hex
(Lit
);
5071 -- Construct the expression using this literal. Note that it is
5072 -- important to qualify the literal with its proper modular type
5073 -- since universal integer does not have the required range and
5074 -- also this is a left justified modular type, which is important
5075 -- in the big-endian case.
5078 Unchecked_Convert_To
(Typ
,
5079 Make_Qualified_Expression
(Loc
,
5081 New_Occurrence_Of
(Packed_Array_Type
(Typ
), Loc
),
5082 Expression
=> Lit
)));
5084 Analyze_And_Resolve
(N
, Typ
);
5092 end Packed_Array_Aggregate_Handled
;
5094 ----------------------------
5095 -- Has_Mutable_Components --
5096 ----------------------------
5098 function Has_Mutable_Components
(Typ
: Entity_Id
) return Boolean is
5102 Comp
:= First_Component
(Typ
);
5104 while Present
(Comp
) loop
5105 if Is_Record_Type
(Etype
(Comp
))
5106 and then Has_Discriminants
(Etype
(Comp
))
5107 and then not Is_Constrained
(Etype
(Comp
))
5112 Next_Component
(Comp
);
5116 end Has_Mutable_Components
;
5118 ------------------------------
5119 -- Initialize_Discriminants --
5120 ------------------------------
5122 procedure Initialize_Discriminants
(N
: Node_Id
; Typ
: Entity_Id
) is
5123 Loc
: constant Source_Ptr
:= Sloc
(N
);
5124 Bas
: constant Entity_Id
:= Base_Type
(Typ
);
5125 Par
: constant Entity_Id
:= Etype
(Bas
);
5126 Decl
: constant Node_Id
:= Parent
(Par
);
5130 if Is_Tagged_Type
(Bas
)
5131 and then Is_Derived_Type
(Bas
)
5132 and then Has_Discriminants
(Par
)
5133 and then Has_Discriminants
(Bas
)
5134 and then Number_Discriminants
(Bas
) /= Number_Discriminants
(Par
)
5135 and then Nkind
(Decl
) = N_Full_Type_Declaration
5136 and then Nkind
(Type_Definition
(Decl
)) = N_Record_Definition
5138 (Variant_Part
(Component_List
(Type_Definition
(Decl
))))
5139 and then Nkind
(N
) /= N_Extension_Aggregate
5142 -- Call init proc to set discriminants.
5143 -- There should eventually be a special procedure for this ???
5145 Ref
:= New_Reference_To
(Defining_Identifier
(N
), Loc
);
5146 Insert_Actions_After
(N
,
5147 Build_Initialization_Call
(Sloc
(N
), Ref
, Typ
));
5149 end Initialize_Discriminants
;
5156 (Obj_Type
: Entity_Id
;
5157 Typ
: Entity_Id
) return Boolean
5159 L1
, L2
, H1
, H2
: Node_Id
;
5161 -- No sliding if the type of the object is not established yet, if
5162 -- it is an unconstrained type whose actual subtype comes from the
5163 -- aggregate, or if the two types are identical.
5165 if not Is_Array_Type
(Obj_Type
) then
5168 elsif not Is_Constrained
(Obj_Type
) then
5171 elsif Typ
= Obj_Type
then
5175 -- Sliding can only occur along the first dimension
5177 Get_Index_Bounds
(First_Index
(Typ
), L1
, H1
);
5178 Get_Index_Bounds
(First_Index
(Obj_Type
), L2
, H2
);
5180 if not Is_Static_Expression
(L1
)
5181 or else not Is_Static_Expression
(L2
)
5182 or else not Is_Static_Expression
(H1
)
5183 or else not Is_Static_Expression
(H2
)
5187 return Expr_Value
(L1
) /= Expr_Value
(L2
)
5188 or else Expr_Value
(H1
) /= Expr_Value
(H2
);
5193 ---------------------------
5194 -- Safe_Slice_Assignment --
5195 ---------------------------
5197 function Safe_Slice_Assignment
(N
: Node_Id
) return Boolean is
5198 Loc
: constant Source_Ptr
:= Sloc
(Parent
(N
));
5199 Pref
: constant Node_Id
:= Prefix
(Name
(Parent
(N
)));
5200 Range_Node
: constant Node_Id
:= Discrete_Range
(Name
(Parent
(N
)));
5208 -- Generate: for J in Range loop Pref (J) := Expr; end loop;
5210 if Comes_From_Source
(N
)
5211 and then No
(Expressions
(N
))
5212 and then Nkind
(First
(Choices
(First
(Component_Associations
(N
)))))
5216 Expression
(First
(Component_Associations
(N
)));
5217 L_J
:= Make_Defining_Identifier
(Loc
, New_Internal_Name
('J'));
5220 Make_Iteration_Scheme
(Loc
,
5221 Loop_Parameter_Specification
=>
5222 Make_Loop_Parameter_Specification
5224 Defining_Identifier
=> L_J
,
5225 Discrete_Subtype_Definition
=> Relocate_Node
(Range_Node
)));
5228 Make_Assignment_Statement
(Loc
,
5230 Make_Indexed_Component
(Loc
,
5231 Prefix
=> Relocate_Node
(Pref
),
5232 Expressions
=> New_List
(New_Occurrence_Of
(L_J
, Loc
))),
5233 Expression
=> Relocate_Node
(Expr
));
5235 -- Construct the final loop
5238 Make_Implicit_Loop_Statement
5239 (Node
=> Parent
(N
),
5240 Identifier
=> Empty
,
5241 Iteration_Scheme
=> L_Iter
,
5242 Statements
=> New_List
(L_Body
));
5244 -- Set type of aggregate to be type of lhs in assignment,
5245 -- to suppress redundant length checks.
5247 Set_Etype
(N
, Etype
(Name
(Parent
(N
))));
5249 Rewrite
(Parent
(N
), Stat
);
5250 Analyze
(Parent
(N
));
5256 end Safe_Slice_Assignment
;
5258 ---------------------
5259 -- Sort_Case_Table --
5260 ---------------------
5262 procedure Sort_Case_Table
(Case_Table
: in out Case_Table_Type
) is
5263 L
: constant Int
:= Case_Table
'First;
5264 U
: constant Int
:= Case_Table
'Last;
5273 T
:= Case_Table
(K
+ 1);
5277 and then Expr_Value
(Case_Table
(J
- 1).Choice_Lo
) >
5278 Expr_Value
(T
.Choice_Lo
)
5280 Case_Table
(J
) := Case_Table
(J
- 1);
5284 Case_Table
(J
) := T
;
5287 end Sort_Case_Table
;