1 ------------------------------------------------------------------------------
3 -- GNAT COMPILER COMPONENTS --
9 -- Copyright (C) 1992-2002 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 Freeze
; use Freeze
;
37 with Hostparm
; use Hostparm
;
38 with Itypes
; use Itypes
;
40 with Nmake
; use Nmake
;
41 with Nlists
; use Nlists
;
42 with Restrict
; use Restrict
;
43 with Rtsfind
; use Rtsfind
;
44 with Ttypes
; use Ttypes
;
46 with Sem_Ch3
; use Sem_Ch3
;
47 with Sem_Eval
; use Sem_Eval
;
48 with Sem_Res
; use Sem_Res
;
49 with Sem_Util
; use Sem_Util
;
50 with Sinfo
; use Sinfo
;
51 with Snames
; use Snames
;
52 with Stand
; use Stand
;
53 with Tbuild
; use Tbuild
;
54 with Uintp
; use Uintp
;
56 package body Exp_Aggr
is
58 type Case_Bounds
is record
61 Choice_Node
: Node_Id
;
64 type Case_Table_Type
is array (Nat
range <>) of Case_Bounds
;
65 -- Table type used by Check_Case_Choices procedure
67 procedure Sort_Case_Table
(Case_Table
: in out Case_Table_Type
);
68 -- Sort the Case Table using the Lower Bound of each Choice as the key.
69 -- A simple insertion sort is used since the number of choices in a case
70 -- statement of variant part will usually be small and probably in near
73 ------------------------------------------------------
74 -- Local subprograms for Record Aggregate Expansion --
75 ------------------------------------------------------
77 procedure Expand_Record_Aggregate
79 Orig_Tag
: Node_Id
:= Empty
;
80 Parent_Expr
: Node_Id
:= Empty
);
81 -- This is the top level procedure for record aggregate expansion.
82 -- Expansion for record aggregates needs expand aggregates for tagged
83 -- record types. Specifically Expand_Record_Aggregate adds the Tag
84 -- field in front of the Component_Association list that was created
85 -- during resolution by Resolve_Record_Aggregate.
87 -- N is the record aggregate node.
88 -- Orig_Tag is the value of the Tag that has to be provided for this
89 -- specific aggregate. It carries the tag corresponding to the type
90 -- of the outermost aggregate during the recursive expansion
91 -- Parent_Expr is the ancestor part of the original extension
94 procedure Convert_To_Assignments
(N
: Node_Id
; Typ
: Entity_Id
);
95 -- N is an N_Aggregate of a N_Extension_Aggregate. Typ is the type of
96 -- the aggregate. Transform the given aggregate into a sequence of
97 -- assignments component per component.
99 function Build_Record_Aggr_Code
103 Flist
: Node_Id
:= Empty
;
104 Obj
: Entity_Id
:= Empty
)
106 -- N is an N_Aggregate or a N_Extension_Aggregate. Typ is the type
107 -- of the aggregate. Target is an expression containing the
108 -- location on which the component by component assignments will
109 -- take place. Returns the list of assignments plus all other
110 -- adjustments needed for tagged and controlled types. Flist is an
111 -- expression representing the finalization list on which to
112 -- attach the controlled components if any. Obj is present in the
113 -- object declaration and dynamic allocation cases, it contains
114 -- an entity that allows to know if the value being created needs to be
115 -- attached to the final list in case of pragma finalize_Storage_Only.
117 procedure Initialize_Discriminants
(N
: Node_Id
; Typ
: Entity_Id
);
118 -- If the type of the aggregate is a type extension with renamed discrimi-
119 -- nants, we must initialize the hidden discriminants of the parent.
120 -- Otherwise, the target object must not be initialized. The discriminants
121 -- are initialized by calling the initialization procedure for the type.
122 -- This is incorrect if the initialization of other components has any
123 -- side effects. We restrict this call to the case where the parent type
124 -- has a variant part, because this is the only case where the hidden
125 -- discriminants are accessed, namely when calling discriminant checking
126 -- functions of the parent type, and when applying a stream attribute to
127 -- an object of the derived type.
129 -----------------------------------------------------
130 -- Local Subprograms for Array Aggregate Expansion --
131 -----------------------------------------------------
133 procedure Convert_To_Positional
135 Max_Others_Replicate
: Nat
:= 5;
136 Handle_Bit_Packed
: Boolean := False);
137 -- If possible, convert named notation to positional notation. This
138 -- conversion is possible only in some static cases. If the conversion
139 -- is possible, then N is rewritten with the analyzed converted
140 -- aggregate. The parameter Max_Others_Replicate controls the maximum
141 -- number of values corresponding to an others choice that will be
142 -- converted to positional notation (the default of 5 is the normal
143 -- limit, and reflects the fact that normally the loop is better than
144 -- a lot of separate assignments). Note that this limit gets overridden
145 -- in any case if either of the restrictions No_Elaboration_Code or
146 -- No_Implicit_Loops is set. The parameter Handle_Bit_Packed is usually
147 -- set False (since we do not expect the back end to handle bit packed
148 -- arrays, so the normal case of conversion is pointless), but in the
149 -- special case of a call from Packed_Array_Aggregate_Handled, we set
150 -- this parameter to True, since these are cases we handle in there.
152 procedure Expand_Array_Aggregate
(N
: Node_Id
);
153 -- This is the top-level routine to perform array aggregate expansion.
154 -- N is the N_Aggregate node to be expanded.
156 function Backend_Processing_Possible
(N
: Node_Id
) return Boolean;
157 -- This function checks if array aggregate N can be processed directly
158 -- by Gigi. If this is the case True is returned.
160 function Build_Array_Aggr_Code
164 Scalar_Comp
: Boolean;
165 Indices
: List_Id
:= No_List
;
166 Flist
: Node_Id
:= Empty
)
168 -- This recursive routine returns a list of statements containing the
169 -- loops and assignments that are needed for the expansion of the array
172 -- N is the (sub-)aggregate node to be expanded into code.
174 -- Index is the index node corresponding to the array sub-aggregate N.
176 -- Into is the target expression into which we are copying the aggregate.
178 -- Scalar_Comp is True if the component type of the aggregate is scalar.
180 -- Indices is the current list of expressions used to index the
181 -- object we are writing into.
183 -- Flist is an expression representing the finalization list on which
184 -- to attach the controlled components if any.
186 function Number_Of_Choices
(N
: Node_Id
) return Nat
;
187 -- Returns the number of discrete choices (not including the others choice
188 -- if present) contained in (sub-)aggregate N.
190 function Late_Expansion
194 Flist
: Node_Id
:= Empty
;
195 Obj
: Entity_Id
:= Empty
)
197 -- N is a nested (record or array) aggregate that has been marked
198 -- with 'Delay_Expansion'. Typ is the expected type of the
199 -- aggregate and Target is a (duplicable) expression that will
200 -- hold the result of the aggregate expansion. Flist is the
201 -- finalization list to be used to attach controlled
202 -- components. 'Obj' when non empty, carries the original object
203 -- being initialized in order to know if it needs to be attached
204 -- to the previous parameter which may not be the case when
205 -- Finalize_Storage_Only is set. Basically this procedure is used
206 -- to implement top-down expansions of nested aggregates. This is
207 -- necessary for avoiding temporaries at each level as well as for
208 -- propagating the right internal finalization list.
210 function Make_OK_Assignment_Statement
213 Expression
: Node_Id
)
215 -- This is like Make_Assignment_Statement, except that Assignment_OK
216 -- is set in the left operand. All assignments built by this unit
217 -- use this routine. This is needed to deal with assignments to
218 -- initialized constants that are done in place.
220 function Packed_Array_Aggregate_Handled
(N
: Node_Id
) return Boolean;
221 -- Given an array aggregate, this function handles the case of a packed
222 -- array aggregate with all constant values, where the aggregate can be
223 -- evaluated at compile time. If this is possible, then N is rewritten
224 -- to be its proper compile time value with all the components properly
225 -- assembled. The expression is analyzed and resolved and True is
226 -- returned. If this transformation is not possible, N is unchanged
227 -- and False is returned
229 function Safe_Slice_Assignment
(N
: Node_Id
) return Boolean;
230 -- If a slice assignment has an aggregate with a single others_choice,
231 -- the assignment can be done in place even if bounds are not static,
232 -- by converting it into a loop over the discrete range of the slice.
234 ---------------------------------
235 -- Backend_Processing_Possible --
236 ---------------------------------
238 -- Backend processing by Gigi/gcc is possible only if all the following
239 -- conditions are met:
241 -- 1. N is fully positional
243 -- 2. N is not a bit-packed array aggregate;
245 -- 3. The size of N's array type must be known at compile time. Note
246 -- that this implies that the component size is also known
248 -- 4. The array type of N does not follow the Fortran layout convention
249 -- or if it does it must be 1 dimensional.
251 -- 5. The array component type is tagged, which may necessitate
252 -- reassignment of proper tags.
254 function Backend_Processing_Possible
(N
: Node_Id
) return Boolean is
255 Typ
: constant Entity_Id
:= Etype
(N
);
256 -- Typ is the correct constrained array subtype of the aggregate.
258 function Static_Check
(N
: Node_Id
; Index
: Node_Id
) return Boolean;
259 -- Recursively checks that N is fully positional, returns true if so.
265 function Static_Check
(N
: Node_Id
; Index
: Node_Id
) return Boolean is
269 -- Check for component associations
271 if Present
(Component_Associations
(N
)) then
275 -- Recurse to check subaggregates, which may appear in qualified
276 -- expressions. If delayed, the front-end will have to expand.
278 Expr
:= First
(Expressions
(N
));
280 while Present
(Expr
) loop
282 if Is_Delayed_Aggregate
(Expr
) then
286 if Present
(Next_Index
(Index
))
287 and then not Static_Check
(Expr
, Next_Index
(Index
))
298 -- Start of processing for Backend_Processing_Possible
301 -- Checks 2 (array must not be bit packed)
303 if Is_Bit_Packed_Array
(Typ
) then
307 -- Checks 4 (array must not be multi-dimensional Fortran case)
309 if Convention
(Typ
) = Convention_Fortran
310 and then Number_Dimensions
(Typ
) > 1
315 -- Checks 3 (size of array must be known at compile time)
317 if not Size_Known_At_Compile_Time
(Typ
) then
321 -- Checks 1 (aggregate must be fully positional)
323 if not Static_Check
(N
, First_Index
(Typ
)) then
327 -- Checks 5 (if the component type is tagged, then we may need
328 -- to do tag adjustments; perhaps this should be refined to
329 -- check for any component associations that actually
330 -- need tag adjustment, along the lines of the test that's
331 -- done in Has_Delayed_Nested_Aggregate_Or_Tagged_Comps
332 -- for record aggregates with tagged components, but not
333 -- clear whether it's worthwhile ???; in the case of the
334 -- JVM, object tags are handled implicitly)
336 if Is_Tagged_Type
(Component_Type
(Typ
)) and then not Java_VM
then
340 -- Backend processing is possible
342 Set_Compile_Time_Known_Aggregate
(N
, True);
343 Set_Size_Known_At_Compile_Time
(Etype
(N
), True);
345 end Backend_Processing_Possible
;
347 ---------------------------
348 -- Build_Array_Aggr_Code --
349 ---------------------------
351 -- The code that we generate from a one dimensional aggregate is
353 -- 1. If the sub-aggregate contains discrete choices we
355 -- (a) Sort the discrete choices
357 -- (b) Otherwise for each discrete choice that specifies a range we
358 -- emit a loop. If a range specifies a maximum of three values, or
359 -- we are dealing with an expression we emit a sequence of
360 -- assignments instead of a loop.
362 -- (c) Generate the remaining loops to cover the others choice if any.
364 -- 2. If the aggregate contains positional elements we
366 -- (a) translate the positional elements in a series of assignments.
368 -- (b) Generate a final loop to cover the others choice if any.
369 -- Note that this final loop has to be a while loop since the case
371 -- L : Integer := Integer'Last;
372 -- H : Integer := Integer'Last;
373 -- A : array (L .. H) := (1, others =>0);
375 -- cannot be handled by a for loop. Thus for the following
377 -- array (L .. H) := (.. positional elements.., others =>E);
379 -- we always generate something like:
381 -- J : Index_Type := Index_Of_Last_Positional_Element;
383 -- J := Index_Base'Succ (J)
387 function Build_Array_Aggr_Code
391 Scalar_Comp
: Boolean;
392 Indices
: List_Id
:= No_List
;
393 Flist
: Node_Id
:= Empty
)
396 Loc
: constant Source_Ptr
:= Sloc
(N
);
397 Index_Base
: constant Entity_Id
:= Base_Type
(Etype
(Index
));
398 Index_Base_L
: constant Node_Id
:= Type_Low_Bound
(Index_Base
);
399 Index_Base_H
: constant Node_Id
:= Type_High_Bound
(Index_Base
);
401 function Add
(Val
: Int
; To
: Node_Id
) return Node_Id
;
402 -- Returns an expression where Val is added to expression To,
403 -- unless To+Val is provably out of To's base type range.
404 -- To must be an already analyzed expression.
406 function Empty_Range
(L
, H
: Node_Id
) return Boolean;
407 -- Returns True if the range defined by L .. H is certainly empty.
409 function Equal
(L
, H
: Node_Id
) return Boolean;
410 -- Returns True if L = H for sure.
412 function Index_Base_Name
return Node_Id
;
413 -- Returns a new reference to the index type name.
415 function Gen_Assign
(Ind
: Node_Id
; Expr
: Node_Id
) return List_Id
;
416 -- Ind must be a side-effect free expression.
417 -- If the input aggregate N to Build_Loop contains no sub-aggregates,
418 -- This routine returns the assignment statement
420 -- Into (Indices, Ind) := Expr;
422 -- Otherwise we call Build_Code recursively.
424 function Gen_Loop
(L
, H
: Node_Id
; Expr
: Node_Id
) return List_Id
;
425 -- Nodes L and H must be side-effect free expressions.
426 -- If the input aggregate N to Build_Loop contains no sub-aggregates,
427 -- This routine returns the for loop statement
429 -- for J in Index_Base'(L) .. Index_Base'(H) loop
430 -- Into (Indices, J) := Expr;
433 -- Otherwise we call Build_Code recursively.
434 -- As an optimization if the loop covers 3 or less scalar elements we
435 -- generate a sequence of assignments.
437 function Gen_While
(L
, H
: Node_Id
; Expr
: Node_Id
) return List_Id
;
438 -- Nodes L and H must be side-effect free expressions.
439 -- If the input aggregate N to Build_Loop contains no sub-aggregates,
440 -- This routine returns the while loop statement
442 -- J : Index_Base := L;
444 -- J := Index_Base'Succ (J);
445 -- Into (Indices, J) := Expr;
448 -- Otherwise we call Build_Code recursively.
450 function Local_Compile_Time_Known_Value
(E
: Node_Id
) return Boolean;
451 function Local_Expr_Value
(E
: Node_Id
) return Uint
;
452 -- These two Local routines are used to replace the corresponding ones
453 -- in sem_eval because while processing the bounds of an aggregate with
454 -- discrete choices whose index type is an enumeration, we build static
455 -- expressions not recognized by Compile_Time_Known_Value as such since
456 -- they have not yet been analyzed and resolved. All the expressions in
457 -- question are things like Index_Base_Name'Val (Const) which we can
458 -- easily recognize as being constant.
464 function Add
(Val
: Int
; To
: Node_Id
) return Node_Id
is
470 U_Val
: Uint
:= UI_From_Int
(Val
);
473 -- Note: do not try to optimize the case of Val = 0, because
474 -- we need to build a new node with the proper Sloc value anyway.
476 -- First test if we can do constant folding
478 if Local_Compile_Time_Known_Value
(To
) then
479 U_To
:= Local_Expr_Value
(To
) + Val
;
481 -- Determine if our constant is outside the range of the index.
482 -- If so return an Empty node. This empty node will be caught
483 -- by Empty_Range below.
485 if Compile_Time_Known_Value
(Index_Base_L
)
486 and then U_To
< Expr_Value
(Index_Base_L
)
490 elsif Compile_Time_Known_Value
(Index_Base_H
)
491 and then U_To
> Expr_Value
(Index_Base_H
)
496 Expr_Pos
:= Make_Integer_Literal
(Loc
, U_To
);
497 Set_Is_Static_Expression
(Expr_Pos
);
499 if not Is_Enumeration_Type
(Index_Base
) then
502 -- If we are dealing with enumeration return
503 -- Index_Base'Val (Expr_Pos)
507 Make_Attribute_Reference
509 Prefix
=> Index_Base_Name
,
510 Attribute_Name
=> Name_Val
,
511 Expressions
=> New_List
(Expr_Pos
));
517 -- If we are here no constant folding possible
519 if not Is_Enumeration_Type
(Index_Base
) then
522 Left_Opnd
=> Duplicate_Subexpr
(To
),
523 Right_Opnd
=> Make_Integer_Literal
(Loc
, U_Val
));
525 -- If we are dealing with enumeration return
526 -- Index_Base'Val (Index_Base'Pos (To) + Val)
530 Make_Attribute_Reference
532 Prefix
=> Index_Base_Name
,
533 Attribute_Name
=> Name_Pos
,
534 Expressions
=> New_List
(Duplicate_Subexpr
(To
)));
539 Right_Opnd
=> Make_Integer_Literal
(Loc
, U_Val
));
542 Make_Attribute_Reference
544 Prefix
=> Index_Base_Name
,
545 Attribute_Name
=> Name_Val
,
546 Expressions
=> New_List
(Expr_Pos
));
556 function Empty_Range
(L
, H
: Node_Id
) return Boolean is
557 Is_Empty
: Boolean := False;
562 -- First check if L or H were already detected as overflowing the
563 -- index base range type by function Add above. If this is so Add
564 -- returns the empty node.
566 if No
(L
) or else No
(H
) then
573 -- L > H range is empty
579 -- B_L > H range must be empty
585 -- L > B_H range must be empty
589 High
:= Index_Base_H
;
592 if Local_Compile_Time_Known_Value
(Low
)
593 and then Local_Compile_Time_Known_Value
(High
)
596 UI_Gt
(Local_Expr_Value
(Low
), Local_Expr_Value
(High
));
609 function Equal
(L
, H
: Node_Id
) return Boolean is
614 elsif Local_Compile_Time_Known_Value
(L
)
615 and then Local_Compile_Time_Known_Value
(H
)
617 return UI_Eq
(Local_Expr_Value
(L
), Local_Expr_Value
(H
));
627 function Gen_Assign
(Ind
: Node_Id
; Expr
: Node_Id
) return List_Id
is
628 L
: List_Id
:= New_List
;
632 New_Indices
: List_Id
;
633 Indexed_Comp
: Node_Id
;
635 Comp_Type
: Entity_Id
:= Empty
;
637 function Add_Loop_Actions
(Lis
: List_Id
) return List_Id
;
638 -- Collect insert_actions generated in the construction of a
639 -- loop, and prepend them to the sequence of assignments to
640 -- complete the eventual body of the loop.
642 ----------------------
643 -- Add_Loop_Actions --
644 ----------------------
646 function Add_Loop_Actions
(Lis
: List_Id
) return List_Id
is
650 if Nkind
(Parent
(Expr
)) = N_Component_Association
651 and then Present
(Loop_Actions
(Parent
(Expr
)))
653 Append_List
(Lis
, Loop_Actions
(Parent
(Expr
)));
654 Res
:= Loop_Actions
(Parent
(Expr
));
655 Set_Loop_Actions
(Parent
(Expr
), No_List
);
661 end Add_Loop_Actions
;
663 -- Start of processing for Gen_Assign
667 New_Indices
:= New_List
;
669 New_Indices
:= New_Copy_List_Tree
(Indices
);
672 Append_To
(New_Indices
, Ind
);
674 if Present
(Flist
) then
675 F
:= New_Copy_Tree
(Flist
);
677 elsif Present
(Etype
(N
)) and then Controlled_Type
(Etype
(N
)) then
678 if Is_Entity_Name
(Into
)
679 and then Present
(Scope
(Entity
(Into
)))
681 F
:= Find_Final_List
(Scope
(Entity
(Into
)));
684 F
:= Find_Final_List
(Current_Scope
);
690 if Present
(Next_Index
(Index
)) then
693 Build_Array_Aggr_Code
694 (Expr
, Next_Index
(Index
),
695 Into
, Scalar_Comp
, New_Indices
, F
));
698 -- If we get here then we are at a bottom-level (sub-)aggregate
700 Indexed_Comp
:= Checks_Off
(
701 Make_Indexed_Component
(Loc
,
702 Prefix
=> New_Copy_Tree
(Into
),
703 Expressions
=> New_Indices
));
705 Set_Assignment_OK
(Indexed_Comp
);
707 if Nkind
(Expr
) = N_Qualified_Expression
then
708 Expr_Q
:= Expression
(Expr
);
713 if Present
(Etype
(N
))
714 and then Etype
(N
) /= Any_Composite
716 Comp_Type
:= Component_Type
(Etype
(N
));
718 elsif Present
(Next
(First
(New_Indices
))) then
720 -- this is a multidimensional array. Recover the component
721 -- type from the outermost aggregate, because subaggregates
722 -- do not have an assigned type.
725 P
: Node_Id
:= Parent
(Expr
);
728 while Present
(P
) loop
730 if Nkind
(P
) = N_Aggregate
731 and then Present
(Etype
(P
))
733 Comp_Type
:= Component_Type
(Etype
(P
));
743 if (Nkind
(Expr_Q
) = N_Aggregate
744 or else Nkind
(Expr_Q
) = N_Extension_Aggregate
)
747 -- At this stage the Expression may not have been
748 -- analyzed yet because the array aggregate code has not
749 -- been updated to use the Expansion_Delayed flag and
750 -- avoid analysis altogether to solve the same problem
751 -- (see Resolve_Aggr_Expr) so let's do the analysis of
752 -- non-array aggregates now in order to get the value of
753 -- Expansion_Delayed flag for the inner aggregate ???
755 if Present
(Comp_Type
) and then not Is_Array_Type
(Comp_Type
) then
756 Analyze_And_Resolve
(Expr_Q
, Comp_Type
);
759 if Is_Delayed_Aggregate
(Expr_Q
) then
762 Late_Expansion
(Expr_Q
, Etype
(Expr_Q
), Indexed_Comp
, F
));
766 -- Now generate the assignment with no associated controlled
767 -- actions since the target of the assignment may not have
768 -- been initialized, it is not possible to Finalize it as
769 -- expected by normal controlled assignment. The rest of the
770 -- controlled actions are done manually with the proper
771 -- finalization list coming from the context.
774 Make_OK_Assignment_Statement
(Loc
,
775 Name
=> Indexed_Comp
,
776 Expression
=> New_Copy_Tree
(Expr
));
778 if Present
(Comp_Type
) and then Controlled_Type
(Comp_Type
) then
779 Set_No_Ctrl_Actions
(A
);
784 -- Adjust the tag if tagged (because of possible view
785 -- conversions), unless compiling for the Java VM
786 -- where tags are implicit.
788 if Present
(Comp_Type
)
789 and then Is_Tagged_Type
(Comp_Type
)
793 Make_OK_Assignment_Statement
(Loc
,
795 Make_Selected_Component
(Loc
,
796 Prefix
=> New_Copy_Tree
(Indexed_Comp
),
798 New_Reference_To
(Tag_Component
(Comp_Type
), Loc
)),
801 Unchecked_Convert_To
(RTE
(RE_Tag
),
803 Access_Disp_Table
(Comp_Type
), Loc
)));
808 -- Adjust and Attach the component to the proper final list
809 -- which can be the controller of the outer record object or
810 -- the final list associated with the scope
812 if Present
(Comp_Type
) and then Controlled_Type
(Comp_Type
) then
815 Ref
=> New_Copy_Tree
(Indexed_Comp
),
818 With_Attach
=> Make_Integer_Literal
(Loc
, 1)));
821 return Add_Loop_Actions
(L
);
828 function Gen_Loop
(L
, H
: Node_Id
; Expr
: Node_Id
) return List_Id
is
832 -- Index_Base'(L) .. Index_Base'(H)
834 L_Iteration_Scheme
: Node_Id
;
835 -- L_J in Index_Base'(L) .. Index_Base'(H)
838 -- The statements to execute in the loop
840 S
: List_Id
:= New_List
;
844 -- Copy of expression tree, used for checking purposes
847 -- If loop bounds define an empty range return the null statement
849 if Empty_Range
(L
, H
) then
850 Append_To
(S
, Make_Null_Statement
(Loc
));
852 -- The expression must be type-checked even though no component
853 -- of the aggregate will have this value. This is done only for
854 -- actual components of the array, not for subaggregates. Do the
855 -- check on a copy, because the expression may be shared among
856 -- several choices, some of which might be non-null.
858 if Present
(Etype
(N
))
859 and then Is_Array_Type
(Etype
(N
))
860 and then No
(Next_Index
(Index
))
862 Expander_Mode_Save_And_Set
(False);
863 Tcopy
:= New_Copy_Tree
(Expr
);
864 Set_Parent
(Tcopy
, N
);
865 Analyze_And_Resolve
(Tcopy
, Component_Type
(Etype
(N
)));
866 Expander_Mode_Restore
;
871 -- If loop bounds are the same then generate an assignment
873 elsif Equal
(L
, H
) then
874 return Gen_Assign
(New_Copy_Tree
(L
), Expr
);
876 -- If H - L <= 2 then generate a sequence of assignments
877 -- when we are processing the bottom most aggregate and it contains
878 -- scalar components.
880 elsif No
(Next_Index
(Index
))
882 and then Local_Compile_Time_Known_Value
(L
)
883 and then Local_Compile_Time_Known_Value
(H
)
884 and then Local_Expr_Value
(H
) - Local_Expr_Value
(L
) <= 2
886 Append_List_To
(S
, Gen_Assign
(New_Copy_Tree
(L
), Expr
));
887 Append_List_To
(S
, Gen_Assign
(Add
(1, To
=> L
), Expr
));
889 if Local_Expr_Value
(H
) - Local_Expr_Value
(L
) = 2 then
890 Append_List_To
(S
, Gen_Assign
(Add
(2, To
=> L
), Expr
));
896 -- Otherwise construct the loop, starting with the loop index L_J
898 L_J
:= Make_Defining_Identifier
(Loc
, New_Internal_Name
('J'));
900 -- Construct "L .. H"
905 Low_Bound
=> Make_Qualified_Expression
907 Subtype_Mark
=> Index_Base_Name
,
909 High_Bound
=> Make_Qualified_Expression
911 Subtype_Mark
=> Index_Base_Name
,
914 -- Construct "for L_J in Index_Base range L .. H"
916 L_Iteration_Scheme
:=
917 Make_Iteration_Scheme
919 Loop_Parameter_Specification
=>
920 Make_Loop_Parameter_Specification
922 Defining_Identifier
=> L_J
,
923 Discrete_Subtype_Definition
=> L_Range
));
925 -- Construct the statements to execute in the loop body
927 L_Body
:= Gen_Assign
(New_Reference_To
(L_J
, Loc
), Expr
);
929 -- Construct the final loop
931 Append_To
(S
, Make_Implicit_Loop_Statement
934 Iteration_Scheme
=> L_Iteration_Scheme
,
935 Statements
=> L_Body
));
946 -- W_J : Index_Base := L;
947 -- while W_J < H loop
948 -- W_J := Index_Base'Succ (W);
952 function Gen_While
(L
, H
: Node_Id
; Expr
: Node_Id
) return List_Id
is
957 -- W_J : Base_Type := L;
959 W_Iteration_Scheme
: Node_Id
;
962 W_Index_Succ
: Node_Id
;
963 -- Index_Base'Succ (J)
965 W_Increment
: Node_Id
;
966 -- W_J := Index_Base'Succ (W)
968 W_Body
: List_Id
:= New_List
;
969 -- The statements to execute in the loop
971 S
: List_Id
:= New_List
;
975 -- If loop bounds define an empty range or are equal return null
977 if Empty_Range
(L
, H
) or else Equal
(L
, H
) then
978 Append_To
(S
, Make_Null_Statement
(Loc
));
982 -- Build the decl of W_J
984 W_J
:= Make_Defining_Identifier
(Loc
, New_Internal_Name
('J'));
986 Make_Object_Declaration
988 Defining_Identifier
=> W_J
,
989 Object_Definition
=> Index_Base_Name
,
992 -- Theoretically we should do a New_Copy_Tree (L) here, but we know
993 -- that in this particular case L is a fresh Expr generated by
994 -- Add which we are the only ones to use.
996 Append_To
(S
, W_Decl
);
998 -- construct " while W_J < H"
1000 W_Iteration_Scheme
:=
1001 Make_Iteration_Scheme
1003 Condition
=> Make_Op_Lt
1005 Left_Opnd
=> New_Reference_To
(W_J
, Loc
),
1006 Right_Opnd
=> New_Copy_Tree
(H
)));
1008 -- Construct the statements to execute in the loop body
1011 Make_Attribute_Reference
1013 Prefix
=> Index_Base_Name
,
1014 Attribute_Name
=> Name_Succ
,
1015 Expressions
=> New_List
(New_Reference_To
(W_J
, Loc
)));
1018 Make_OK_Assignment_Statement
1020 Name
=> New_Reference_To
(W_J
, Loc
),
1021 Expression
=> W_Index_Succ
);
1023 Append_To
(W_Body
, W_Increment
);
1024 Append_List_To
(W_Body
,
1025 Gen_Assign
(New_Reference_To
(W_J
, Loc
), Expr
));
1027 -- Construct the final loop
1029 Append_To
(S
, Make_Implicit_Loop_Statement
1031 Identifier
=> Empty
,
1032 Iteration_Scheme
=> W_Iteration_Scheme
,
1033 Statements
=> W_Body
));
1038 ---------------------
1039 -- Index_Base_Name --
1040 ---------------------
1042 function Index_Base_Name
return Node_Id
is
1044 return New_Reference_To
(Index_Base
, Sloc
(N
));
1045 end Index_Base_Name
;
1047 ------------------------------------
1048 -- Local_Compile_Time_Known_Value --
1049 ------------------------------------
1051 function Local_Compile_Time_Known_Value
(E
: Node_Id
) return Boolean is
1053 return Compile_Time_Known_Value
(E
)
1055 (Nkind
(E
) = N_Attribute_Reference
1056 and then Attribute_Name
(E
) = Name_Val
1057 and then Compile_Time_Known_Value
(First
(Expressions
(E
))));
1058 end Local_Compile_Time_Known_Value
;
1060 ----------------------
1061 -- Local_Expr_Value --
1062 ----------------------
1064 function Local_Expr_Value
(E
: Node_Id
) return Uint
is
1066 if Compile_Time_Known_Value
(E
) then
1067 return Expr_Value
(E
);
1069 return Expr_Value
(First
(Expressions
(E
)));
1071 end Local_Expr_Value
;
1073 -- Build_Array_Aggr_Code Variables
1079 Others_Expr
: Node_Id
:= Empty
;
1081 Aggr_L
: constant Node_Id
:= Low_Bound
(Aggregate_Bounds
(N
));
1082 Aggr_H
: constant Node_Id
:= High_Bound
(Aggregate_Bounds
(N
));
1083 -- The aggregate bounds of this specific sub-aggregate. Note that if
1084 -- the code generated by Build_Array_Aggr_Code is executed then these
1085 -- bounds are OK. Otherwise a Constraint_Error would have been raised.
1087 Aggr_Low
: constant Node_Id
:= Duplicate_Subexpr
(Aggr_L
);
1088 Aggr_High
: constant Node_Id
:= Duplicate_Subexpr
(Aggr_H
);
1089 -- After Duplicate_Subexpr these are side-effect free.
1094 Nb_Choices
: Nat
:= 0;
1095 Table
: Case_Table_Type
(1 .. Number_Of_Choices
(N
));
1096 -- Used to sort all the different choice values
1099 -- Number of elements in the positional aggregate
1101 New_Code
: List_Id
:= New_List
;
1103 -- Start of processing for Build_Array_Aggr_Code
1106 -- STEP 1: Process component associations
1108 if No
(Expressions
(N
)) then
1110 -- STEP 1 (a): Sort the discrete choices
1112 Assoc
:= First
(Component_Associations
(N
));
1113 while Present
(Assoc
) loop
1115 Choice
:= First
(Choices
(Assoc
));
1116 while Present
(Choice
) loop
1118 if Nkind
(Choice
) = N_Others_Choice
then
1119 Others_Expr
:= Expression
(Assoc
);
1123 Get_Index_Bounds
(Choice
, Low
, High
);
1125 Nb_Choices
:= Nb_Choices
+ 1;
1126 Table
(Nb_Choices
) := (Choice_Lo
=> Low
,
1128 Choice_Node
=> Expression
(Assoc
));
1136 -- If there is more than one set of choices these must be static
1137 -- and we can therefore sort them. Remember that Nb_Choices does not
1138 -- account for an others choice.
1140 if Nb_Choices
> 1 then
1141 Sort_Case_Table
(Table
);
1144 -- STEP 1 (b): take care of the whole set of discrete choices.
1146 for J
in 1 .. Nb_Choices
loop
1147 Low
:= Table
(J
).Choice_Lo
;
1148 High
:= Table
(J
).Choice_Hi
;
1149 Expr
:= Table
(J
).Choice_Node
;
1151 Append_List
(Gen_Loop
(Low
, High
, Expr
), To
=> New_Code
);
1154 -- STEP 1 (c): generate the remaining loops to cover others choice
1155 -- We don't need to generate loops over empty gaps, but if there is
1156 -- a single empty range we must analyze the expression for semantics
1158 if Present
(Others_Expr
) then
1160 First
: Boolean := True;
1163 for J
in 0 .. Nb_Choices
loop
1168 Low
:= Add
(1, To
=> Table
(J
).Choice_Hi
);
1171 if J
= Nb_Choices
then
1174 High
:= Add
(-1, To
=> Table
(J
+ 1).Choice_Lo
);
1177 -- If this is an expansion within an init_proc, make
1178 -- sure that discriminant references are replaced by
1179 -- the corresponding discriminal.
1181 if Inside_Init_Proc
then
1182 if Is_Entity_Name
(Low
)
1183 and then Ekind
(Entity
(Low
)) = E_Discriminant
1185 Set_Entity
(Low
, Discriminal
(Entity
(Low
)));
1188 if Is_Entity_Name
(High
)
1189 and then Ekind
(Entity
(High
)) = E_Discriminant
1191 Set_Entity
(High
, Discriminal
(Entity
(High
)));
1196 or else not Empty_Range
(Low
, High
)
1200 (Gen_Loop
(Low
, High
, Others_Expr
), To
=> New_Code
);
1206 -- STEP 2: Process positional components
1209 -- STEP 2 (a): Generate the assignments for each positional element
1210 -- Note that here we have to use Aggr_L rather than Aggr_Low because
1211 -- Aggr_L is analyzed and Add wants an analyzed expression.
1213 Expr
:= First
(Expressions
(N
));
1216 while Present
(Expr
) loop
1217 Nb_Elements
:= Nb_Elements
+ 1;
1218 Append_List
(Gen_Assign
(Add
(Nb_Elements
, To
=> Aggr_L
), Expr
),
1223 -- STEP 2 (b): Generate final loop if an others choice is present
1224 -- Here Nb_Elements gives the offset of the last positional element.
1226 if Present
(Component_Associations
(N
)) then
1227 Assoc
:= Last
(Component_Associations
(N
));
1228 Expr
:= Expression
(Assoc
);
1230 Append_List
(Gen_While
(Add
(Nb_Elements
, To
=> Aggr_L
),
1238 end Build_Array_Aggr_Code
;
1240 ----------------------------
1241 -- Build_Record_Aggr_Code --
1242 ----------------------------
1244 function Build_Record_Aggr_Code
1248 Flist
: Node_Id
:= Empty
;
1249 Obj
: Entity_Id
:= Empty
)
1252 Loc
: constant Source_Ptr
:= Sloc
(N
);
1253 L
: constant List_Id
:= New_List
;
1254 Start_L
: constant List_Id
:= New_List
;
1255 N_Typ
: constant Entity_Id
:= Etype
(N
);
1261 Comp_Type
: Entity_Id
;
1262 Selector
: Entity_Id
;
1263 Comp_Expr
: Node_Id
;
1264 Comp_Kind
: Node_Kind
;
1267 Internal_Final_List
: Node_Id
;
1269 -- If this is an internal aggregate, the External_Final_List is an
1270 -- expression for the controller record of the enclosing type.
1271 -- If the current aggregate has several controlled components, this
1272 -- expression will appear in several calls to attach to the finali-
1273 -- zation list, and it must not be shared.
1275 External_Final_List
: Node_Id
;
1276 Ancestor_Is_Expression
: Boolean := False;
1277 Ancestor_Is_Subtype_Mark
: Boolean := False;
1279 Init_Typ
: Entity_Id
:= Empty
;
1282 function Get_Constraint_Association
(T
: Entity_Id
) return Node_Id
;
1283 -- Returns the first discriminant association in the constraint
1284 -- associated with T, if any, otherwise returns Empty.
1286 function Ancestor_Discriminant_Value
(Disc
: Entity_Id
) return Node_Id
;
1287 -- Returns the value that the given discriminant of an ancestor
1288 -- type should receive (in the absence of a conflict with the
1289 -- value provided by an ancestor part of an extension aggregate).
1291 procedure Check_Ancestor_Discriminants
(Anc_Typ
: Entity_Id
);
1292 -- Check that each of the discriminant values defined by the
1293 -- ancestor part of an extension aggregate match the corresponding
1294 -- values provided by either an association of the aggregate or
1295 -- by the constraint imposed by a parent type (RM95-4.3.2(8)).
1297 function Init_Controller
1304 -- returns the list of statements necessary to initialize the internal
1305 -- controller of the (possible) ancestor typ into target and attach
1306 -- it to finalization list F. Init_Pr conditions the call to the
1307 -- init_proc since it may already be done due to ancestor initialization
1309 ---------------------------------
1310 -- Ancestor_Discriminant_Value --
1311 ---------------------------------
1313 function Ancestor_Discriminant_Value
(Disc
: Entity_Id
) return Node_Id
is
1315 Assoc_Elmt
: Elmt_Id
;
1316 Aggr_Comp
: Entity_Id
;
1317 Corresp_Disc
: Entity_Id
;
1318 Current_Typ
: Entity_Id
:= Base_Type
(Typ
);
1319 Parent_Typ
: Entity_Id
;
1320 Parent_Disc
: Entity_Id
;
1321 Save_Assoc
: Node_Id
:= Empty
;
1324 -- First check any discriminant associations to see if
1325 -- any of them provide a value for the discriminant.
1327 if Present
(Discriminant_Specifications
(Parent
(Current_Typ
))) then
1328 Assoc
:= First
(Component_Associations
(N
));
1329 while Present
(Assoc
) loop
1330 Aggr_Comp
:= Entity
(First
(Choices
(Assoc
)));
1332 if Ekind
(Aggr_Comp
) = E_Discriminant
then
1333 Save_Assoc
:= Expression
(Assoc
);
1335 Corresp_Disc
:= Corresponding_Discriminant
(Aggr_Comp
);
1336 while Present
(Corresp_Disc
) loop
1337 -- If found a corresponding discriminant then return
1338 -- the value given in the aggregate. (Note: this is
1339 -- not correct in the presence of side effects. ???)
1341 if Disc
= Corresp_Disc
then
1342 return Duplicate_Subexpr
(Expression
(Assoc
));
1345 Corresponding_Discriminant
(Corresp_Disc
);
1353 -- No match found in aggregate, so chain up parent types to find
1354 -- a constraint that defines the value of the discriminant.
1356 Parent_Typ
:= Etype
(Current_Typ
);
1357 while Current_Typ
/= Parent_Typ
loop
1358 if Has_Discriminants
(Parent_Typ
) then
1359 Parent_Disc
:= First_Discriminant
(Parent_Typ
);
1361 -- We either get the association from the subtype indication
1362 -- of the type definition itself, or from the discriminant
1363 -- constraint associated with the type entity (which is
1364 -- preferable, but it's not always present ???)
1366 if Is_Empty_Elmt_List
(
1367 Discriminant_Constraint
(Current_Typ
))
1369 Assoc
:= Get_Constraint_Association
(Current_Typ
);
1370 Assoc_Elmt
:= No_Elmt
;
1373 First_Elmt
(Discriminant_Constraint
(Current_Typ
));
1374 Assoc
:= Node
(Assoc_Elmt
);
1377 -- Traverse the discriminants of the parent type looking
1378 -- for one that corresponds.
1380 while Present
(Parent_Disc
) and then Present
(Assoc
) loop
1381 Corresp_Disc
:= Parent_Disc
;
1382 while Present
(Corresp_Disc
)
1383 and then Disc
/= Corresp_Disc
1386 Corresponding_Discriminant
(Corresp_Disc
);
1389 if Disc
= Corresp_Disc
then
1390 if Nkind
(Assoc
) = N_Discriminant_Association
then
1391 Assoc
:= Expression
(Assoc
);
1394 -- If the located association directly denotes
1395 -- a discriminant, then use the value of a saved
1396 -- association of the aggregate. This is a kludge
1397 -- to handle certain cases involving multiple
1398 -- discriminants mapped to a single discriminant
1399 -- of a descendant. It's not clear how to locate the
1400 -- appropriate discriminant value for such cases. ???
1402 if Is_Entity_Name
(Assoc
)
1403 and then Ekind
(Entity
(Assoc
)) = E_Discriminant
1405 Assoc
:= Save_Assoc
;
1408 return Duplicate_Subexpr
(Assoc
);
1411 Next_Discriminant
(Parent_Disc
);
1413 if No
(Assoc_Elmt
) then
1416 Next_Elmt
(Assoc_Elmt
);
1417 if Present
(Assoc_Elmt
) then
1418 Assoc
:= Node
(Assoc_Elmt
);
1426 Current_Typ
:= Parent_Typ
;
1427 Parent_Typ
:= Etype
(Current_Typ
);
1430 -- In some cases there's no ancestor value to locate (such as
1431 -- when an ancestor part given by an expression defines the
1432 -- discriminant value).
1435 end Ancestor_Discriminant_Value
;
1437 ----------------------------------
1438 -- Check_Ancestor_Discriminants --
1439 ----------------------------------
1441 procedure Check_Ancestor_Discriminants
(Anc_Typ
: Entity_Id
) is
1442 Discr
: Entity_Id
:= First_Discriminant
(Base_Type
(Anc_Typ
));
1443 Disc_Value
: Node_Id
;
1447 while Present
(Discr
) loop
1448 Disc_Value
:= Ancestor_Discriminant_Value
(Discr
);
1450 if Present
(Disc_Value
) then
1451 Cond
:= Make_Op_Ne
(Loc
,
1453 Make_Selected_Component
(Loc
,
1454 Prefix
=> New_Copy_Tree
(Target
),
1455 Selector_Name
=> New_Occurrence_Of
(Discr
, Loc
)),
1456 Right_Opnd
=> Disc_Value
);
1459 Make_Raise_Constraint_Error
(Loc
,
1461 Reason
=> CE_Discriminant_Check_Failed
));
1464 Next_Discriminant
(Discr
);
1466 end Check_Ancestor_Discriminants
;
1468 --------------------------------
1469 -- Get_Constraint_Association --
1470 --------------------------------
1472 function Get_Constraint_Association
(T
: Entity_Id
) return Node_Id
is
1473 Typ_Def
: constant Node_Id
:= Type_Definition
(Parent
(T
));
1474 Indic
: constant Node_Id
:= Subtype_Indication
(Typ_Def
);
1477 -- ??? Also need to cover case of a type mark denoting a subtype
1480 if Nkind
(Indic
) = N_Subtype_Indication
1481 and then Present
(Constraint
(Indic
))
1483 return First
(Constraints
(Constraint
(Indic
)));
1487 end Get_Constraint_Association
;
1489 ---------------------
1490 -- Init_controller --
1491 ---------------------
1493 function Init_Controller
1502 L
: List_Id
:= New_List
;
1505 -- _init_proc (target._controller);
1506 -- initialize (target._controller);
1507 -- Attach_to_Final_List (target._controller, F);
1509 Ref
:= Make_Selected_Component
(Loc
,
1510 Prefix
=> Convert_To
(Typ
, New_Copy_Tree
(Target
)),
1511 Selector_Name
=> Make_Identifier
(Loc
, Name_uController
));
1512 Set_Assignment_OK
(Ref
);
1516 Build_Initialization_Call
(Loc
,
1518 Typ
=> RTE
(RE_Record_Controller
),
1519 In_Init_Proc
=> Within_Init_Proc
));
1523 Make_Procedure_Call_Statement
(Loc
,
1525 New_Reference_To
(Find_Prim_Op
(RTE
(RE_Record_Controller
),
1526 Name_Initialize
), Loc
),
1527 Parameter_Associations
=> New_List
(New_Copy_Tree
(Ref
))));
1531 Obj_Ref
=> New_Copy_Tree
(Ref
),
1533 With_Attach
=> Attach
));
1535 end Init_Controller
;
1537 -- Start of processing for Build_Record_Aggr_Code
1541 -- Deal with the ancestor part of extension aggregates
1542 -- or with the discriminants of the root type
1544 if Nkind
(N
) = N_Extension_Aggregate
then
1546 A
: constant Node_Id
:= Ancestor_Part
(N
);
1550 -- If the ancestor part is a subtype mark "T", we generate
1551 -- _init_proc (T(tmp)); if T is constrained and
1552 -- _init_proc (S(tmp)); where S applies an appropriate
1553 -- constraint if T is unconstrained
1555 if Is_Entity_Name
(A
) and then Is_Type
(Entity
(A
)) then
1557 Ancestor_Is_Subtype_Mark
:= True;
1559 if Is_Constrained
(Entity
(A
)) then
1560 Init_Typ
:= Entity
(A
);
1562 -- For an ancestor part given by an unconstrained type
1563 -- mark, create a subtype constrained by appropriate
1564 -- corresponding discriminant values coming from either
1565 -- associations of the aggregate or a constraint on
1566 -- a parent type. The subtype will be used to generate
1567 -- the correct default value for the ancestor part.
1569 elsif Has_Discriminants
(Entity
(A
)) then
1571 Anc_Typ
: Entity_Id
:= Entity
(A
);
1572 Discrim
: Entity_Id
:= First_Discriminant
(Anc_Typ
);
1573 Anc_Constr
: List_Id
:= New_List
;
1574 Disc_Value
: Node_Id
;
1575 New_Indic
: Node_Id
;
1576 Subt_Decl
: Node_Id
;
1578 while Present
(Discrim
) loop
1579 Disc_Value
:= Ancestor_Discriminant_Value
(Discrim
);
1580 Append_To
(Anc_Constr
, Disc_Value
);
1581 Next_Discriminant
(Discrim
);
1585 Make_Subtype_Indication
(Loc
,
1586 Subtype_Mark
=> New_Occurrence_Of
(Anc_Typ
, Loc
),
1588 Make_Index_Or_Discriminant_Constraint
(Loc
,
1589 Constraints
=> Anc_Constr
));
1591 Init_Typ
:= Create_Itype
(Ekind
(Anc_Typ
), N
);
1594 Make_Subtype_Declaration
(Loc
,
1595 Defining_Identifier
=> Init_Typ
,
1596 Subtype_Indication
=> New_Indic
);
1598 -- Itypes must be analyzed with checks off
1599 -- Declaration must have a parent for proper
1600 -- handling of subsidiary actions.
1602 Set_Parent
(Subt_Decl
, N
);
1603 Analyze
(Subt_Decl
, Suppress
=> All_Checks
);
1607 Ref
:= Convert_To
(Init_Typ
, New_Copy_Tree
(Target
));
1608 Set_Assignment_OK
(Ref
);
1610 Append_List_To
(Start_L
,
1611 Build_Initialization_Call
(Loc
,
1614 In_Init_Proc
=> Within_Init_Proc
));
1616 if Is_Constrained
(Entity
(A
))
1617 and then Has_Discriminants
(Entity
(A
))
1619 Check_Ancestor_Discriminants
(Entity
(A
));
1622 -- If the ancestor part is an expression "E", we generate
1626 Ancestor_Is_Expression
:= True;
1627 Init_Typ
:= Etype
(A
);
1629 -- Assign the tag before doing the assignment to make sure
1630 -- that the dispatching call in the subsequent deep_adjust
1631 -- works properly (unless Java_VM, where tags are implicit).
1635 Make_OK_Assignment_Statement
(Loc
,
1637 Make_Selected_Component
(Loc
,
1638 Prefix
=> New_Copy_Tree
(Target
),
1639 Selector_Name
=> New_Reference_To
(
1640 Tag_Component
(Base_Type
(Typ
)), Loc
)),
1643 Unchecked_Convert_To
(RTE
(RE_Tag
),
1645 Access_Disp_Table
(Base_Type
(Typ
)), Loc
)));
1647 Set_Assignment_OK
(Name
(Instr
));
1648 Append_To
(L
, Instr
);
1651 -- If the ancestor part is an aggregate, force its full
1652 -- expansion, which was delayed.
1654 if Nkind
(A
) = N_Qualified_Expression
1655 and then (Nkind
(Expression
(A
)) = N_Aggregate
1657 Nkind
(Expression
(A
)) = N_Extension_Aggregate
)
1659 Set_Analyzed
(A
, False);
1660 Set_Analyzed
(Expression
(A
), False);
1663 Ref
:= Convert_To
(Init_Typ
, New_Copy_Tree
(Target
));
1664 Set_Assignment_OK
(Ref
);
1666 Make_Unsuppress_Block
(Loc
,
1667 Name_Discriminant_Check
,
1669 Make_OK_Assignment_Statement
(Loc
,
1671 Expression
=> A
))));
1673 if Has_Discriminants
(Init_Typ
) then
1674 Check_Ancestor_Discriminants
(Init_Typ
);
1680 -- Generate the discriminant expressions, component by component.
1681 -- If the base type is an unchecked union, the discriminants are
1682 -- unknown to the back-end and absent from a value of the type, so
1683 -- assignments for them are not emitted.
1685 if Has_Discriminants
(Typ
)
1686 and then not Is_Unchecked_Union
(Base_Type
(Typ
))
1689 -- ??? The discriminants of the object not inherited in the type
1690 -- of the object should be initialized here
1694 -- Generate discriminant init values
1697 Discriminant
: Entity_Id
;
1698 Discriminant_Value
: Node_Id
;
1701 Discriminant
:= First_Girder_Discriminant
(Typ
);
1703 while Present
(Discriminant
) loop
1706 Make_Selected_Component
(Loc
,
1707 Prefix
=> New_Copy_Tree
(Target
),
1708 Selector_Name
=> New_Occurrence_Of
(Discriminant
, Loc
));
1710 Discriminant_Value
:=
1711 Get_Discriminant_Value
(
1714 Discriminant_Constraint
(N_Typ
));
1717 Make_OK_Assignment_Statement
(Loc
,
1719 Expression
=> New_Copy_Tree
(Discriminant_Value
));
1721 Set_No_Ctrl_Actions
(Instr
);
1722 Append_To
(L
, Instr
);
1724 Next_Girder_Discriminant
(Discriminant
);
1730 -- Generate the assignments, component by component
1732 -- tmp.comp1 := Expr1_From_Aggr;
1733 -- tmp.comp2 := Expr2_From_Aggr;
1736 Comp
:= First
(Component_Associations
(N
));
1737 while Present
(Comp
) loop
1738 Selector
:= Entity
(First
(Choices
(Comp
)));
1740 if Ekind
(Selector
) /= E_Discriminant
1741 or else Nkind
(N
) = N_Extension_Aggregate
1743 Comp_Type
:= Etype
(Selector
);
1744 Comp_Kind
:= Nkind
(Expression
(Comp
));
1746 Make_Selected_Component
(Loc
,
1747 Prefix
=> New_Copy_Tree
(Target
),
1748 Selector_Name
=> New_Occurrence_Of
(Selector
, Loc
));
1750 if Nkind
(Expression
(Comp
)) = N_Qualified_Expression
then
1751 Expr_Q
:= Expression
(Expression
(Comp
));
1753 Expr_Q
:= Expression
(Comp
);
1756 -- The controller is the one of the parent type defining
1757 -- the component (in case of inherited components).
1759 if Controlled_Type
(Comp_Type
) then
1760 Internal_Final_List
:=
1761 Make_Selected_Component
(Loc
,
1762 Prefix
=> Convert_To
(
1763 Scope
(Original_Record_Component
(Selector
)),
1764 New_Copy_Tree
(Target
)),
1766 Make_Identifier
(Loc
, Name_uController
));
1767 Internal_Final_List
:=
1768 Make_Selected_Component
(Loc
,
1769 Prefix
=> Internal_Final_List
,
1770 Selector_Name
=> Make_Identifier
(Loc
, Name_F
));
1772 -- The internal final list can be part of a constant object
1774 Set_Assignment_OK
(Internal_Final_List
);
1776 Internal_Final_List
:= Empty
;
1779 if Is_Delayed_Aggregate
(Expr_Q
) then
1781 Late_Expansion
(Expr_Q
, Comp_Type
, Comp_Expr
,
1782 Internal_Final_List
));
1785 Make_OK_Assignment_Statement
(Loc
,
1787 Expression
=> Expression
(Comp
));
1789 Set_No_Ctrl_Actions
(Instr
);
1790 Append_To
(L
, Instr
);
1792 -- Adjust the tag if tagged (because of possible view
1793 -- conversions), unless compiling for the Java VM
1794 -- where tags are implicit.
1796 -- tmp.comp._tag := comp_typ'tag;
1798 if Is_Tagged_Type
(Comp_Type
) and then not Java_VM
then
1800 Make_OK_Assignment_Statement
(Loc
,
1802 Make_Selected_Component
(Loc
,
1803 Prefix
=> New_Copy_Tree
(Comp_Expr
),
1805 New_Reference_To
(Tag_Component
(Comp_Type
), Loc
)),
1808 Unchecked_Convert_To
(RTE
(RE_Tag
),
1810 Access_Disp_Table
(Comp_Type
), Loc
)));
1812 Append_To
(L
, Instr
);
1815 -- Adjust and Attach the component to the proper controller
1816 -- Adjust (tmp.comp);
1817 -- Attach_To_Final_List (tmp.comp,
1818 -- comp_typ (tmp)._record_controller.f)
1820 if Controlled_Type
(Comp_Type
) then
1823 Ref
=> New_Copy_Tree
(Comp_Expr
),
1825 Flist_Ref
=> Internal_Final_List
,
1826 With_Attach
=> Make_Integer_Literal
(Loc
, 1)));
1834 -- If the type is tagged, the tag needs to be initialized (unless
1835 -- compiling for the Java VM where tags are implicit). It is done
1836 -- late in the initialization process because in some cases, we call
1837 -- the init_proc of an ancestor which will not leave out the right tag
1839 if Ancestor_Is_Expression
then
1842 elsif Is_Tagged_Type
(Typ
) and then not Java_VM
then
1844 Make_OK_Assignment_Statement
(Loc
,
1846 Make_Selected_Component
(Loc
,
1847 Prefix
=> New_Copy_Tree
(Target
),
1849 New_Reference_To
(Tag_Component
(Base_Type
(Typ
)), Loc
)),
1852 Unchecked_Convert_To
(RTE
(RE_Tag
),
1853 New_Reference_To
(Access_Disp_Table
(Base_Type
(Typ
)), Loc
)));
1855 Append_To
(L
, Instr
);
1858 -- Now deal with the various controlled type data structure
1862 and then Finalize_Storage_Only
(Typ
)
1863 and then (Is_Library_Level_Entity
(Obj
)
1864 or else Entity
(Constant_Value
(RTE
(RE_Garbage_Collected
)))
1867 Attach
:= Make_Integer_Literal
(Loc
, 0);
1869 elsif Nkind
(Parent
(N
)) = N_Qualified_Expression
1870 and then Nkind
(Parent
(Parent
(N
))) = N_Allocator
1872 Attach
:= Make_Integer_Literal
(Loc
, 2);
1875 Attach
:= Make_Integer_Literal
(Loc
, 1);
1878 -- Determine the external finalization list. It is either the
1879 -- finalization list of the outer-scope or the one coming from
1880 -- an outer aggregate. When the target is not a temporary, the
1881 -- proper scope is the scope of the target rather than the
1882 -- potentially transient current scope.
1884 if Controlled_Type
(Typ
) then
1885 if Present
(Flist
) then
1886 External_Final_List
:= New_Copy_Tree
(Flist
);
1888 elsif Is_Entity_Name
(Target
)
1889 and then Present
(Scope
(Entity
(Target
)))
1891 External_Final_List
:= Find_Final_List
(Scope
(Entity
(Target
)));
1894 External_Final_List
:= Find_Final_List
(Current_Scope
);
1898 External_Final_List
:= Empty
;
1901 -- initialize and attach the outer object in the is_controlled
1904 if Is_Controlled
(Typ
) then
1905 if Ancestor_Is_Subtype_Mark
then
1906 Ref
:= Convert_To
(Init_Typ
, New_Copy_Tree
(Target
));
1907 Set_Assignment_OK
(Ref
);
1909 Make_Procedure_Call_Statement
(Loc
,
1910 Name
=> New_Reference_To
(
1911 Find_Prim_Op
(Init_Typ
, Name_Initialize
), Loc
),
1912 Parameter_Associations
=> New_List
(New_Copy_Tree
(Ref
))));
1915 -- ??? when the ancestor part is an expression, the global
1916 -- object is already attached at the wrong level. It should
1917 -- be detached and re-attached. We have a design problem here.
1919 if Ancestor_Is_Expression
1920 and then Has_Controlled_Component
(Init_Typ
)
1924 elsif Has_Controlled_Component
(Typ
) then
1925 F
:= Make_Selected_Component
(Loc
,
1926 Prefix
=> New_Copy_Tree
(Target
),
1927 Selector_Name
=> Make_Identifier
(Loc
, Name_uController
));
1928 F
:= Make_Selected_Component
(Loc
,
1930 Selector_Name
=> Make_Identifier
(Loc
, Name_F
));
1932 Ref
:= New_Copy_Tree
(Target
);
1933 Set_Assignment_OK
(Ref
);
1939 With_Attach
=> Make_Integer_Literal
(Loc
, 1)));
1941 else -- is_Controlled (Typ) and not Has_Controlled_Component (Typ)
1942 Ref
:= New_Copy_Tree
(Target
);
1943 Set_Assignment_OK
(Ref
);
1947 Flist_Ref
=> New_Copy_Tree
(External_Final_List
),
1948 With_Attach
=> Attach
));
1952 -- in the Has_Controlled component case, all the intermediate
1953 -- controllers must be initialized
1955 if Has_Controlled_Component
(Typ
) then
1957 Inner_Typ
: Entity_Id
;
1958 Outer_Typ
: Entity_Id
;
1963 Outer_Typ
:= Base_Type
(Typ
);
1965 -- find outer type with a controller
1967 while Outer_Typ
/= Init_Typ
1968 and then not Has_New_Controlled_Component
(Outer_Typ
)
1970 Outer_Typ
:= Etype
(Outer_Typ
);
1973 -- attach it to the outer record controller to the
1974 -- external final list
1976 if Outer_Typ
= Init_Typ
then
1977 Append_List_To
(Start_L
,
1981 F
=> External_Final_List
,
1983 Init_Pr
=> Ancestor_Is_Expression
));
1985 Inner_Typ
:= Init_Typ
;
1988 Append_List_To
(Start_L
,
1992 F
=> External_Final_List
,
1996 Inner_Typ
:= Etype
(Outer_Typ
);
1998 not Is_Tagged_Type
(Typ
) or else Inner_Typ
= Outer_Typ
;
2001 -- Initialize the internal controllers for tagged types with
2002 -- more than one controller.
2004 while not At_Root
and then Inner_Typ
/= Init_Typ
loop
2005 if Has_New_Controlled_Component
(Inner_Typ
) then
2007 Make_Selected_Component
(Loc
,
2008 Prefix
=> Convert_To
(Outer_Typ
, New_Copy_Tree
(Target
)),
2010 Make_Identifier
(Loc
, Name_uController
));
2011 F
:= Make_Selected_Component
(Loc
,
2013 Selector_Name
=> Make_Identifier
(Loc
, Name_F
));
2014 Append_List_To
(Start_L
,
2019 Attach
=> Make_Integer_Literal
(Loc
, 1),
2021 Outer_Typ
:= Inner_Typ
;
2026 At_Root
:= Inner_Typ
= Etype
(Inner_Typ
);
2027 Inner_Typ
:= Etype
(Inner_Typ
);
2030 -- if not done yet attach the controller of the ancestor part
2032 if Outer_Typ
/= Init_Typ
2033 and then Inner_Typ
= Init_Typ
2034 and then Has_Controlled_Component
(Init_Typ
)
2037 Make_Selected_Component
(Loc
,
2038 Prefix
=> Convert_To
(Outer_Typ
, New_Copy_Tree
(Target
)),
2039 Selector_Name
=> Make_Identifier
(Loc
, Name_uController
));
2040 F
:= Make_Selected_Component
(Loc
,
2042 Selector_Name
=> Make_Identifier
(Loc
, Name_F
));
2044 Attach
:= Make_Integer_Literal
(Loc
, 1);
2045 Append_List_To
(Start_L
,
2051 Init_Pr
=> Ancestor_Is_Expression
));
2056 Append_List_To
(Start_L
, L
);
2058 end Build_Record_Aggr_Code
;
2060 -------------------------------
2061 -- Convert_Aggr_In_Allocator --
2062 -------------------------------
2064 procedure Convert_Aggr_In_Allocator
(Decl
, Aggr
: Node_Id
) is
2065 Loc
: constant Source_Ptr
:= Sloc
(Aggr
);
2066 Typ
: constant Entity_Id
:= Etype
(Aggr
);
2067 Temp
: constant Entity_Id
:= Defining_Identifier
(Decl
);
2068 Occ
: constant Node_Id
:= Unchecked_Convert_To
(Typ
,
2069 Make_Explicit_Dereference
(Loc
, New_Reference_To
(Temp
, Loc
)));
2071 Access_Type
: constant Entity_Id
:= Etype
(Temp
);
2074 Insert_Actions_After
(Decl
,
2075 Late_Expansion
(Aggr
, Typ
, Occ
,
2076 Find_Final_List
(Access_Type
),
2077 Associated_Final_Chain
(Base_Type
(Access_Type
))));
2078 end Convert_Aggr_In_Allocator
;
2080 --------------------------------
2081 -- Convert_Aggr_In_Assignment --
2082 --------------------------------
2084 procedure Convert_Aggr_In_Assignment
(N
: Node_Id
) is
2085 Aggr
: Node_Id
:= Expression
(N
);
2086 Typ
: constant Entity_Id
:= Etype
(Aggr
);
2087 Occ
: constant Node_Id
:= New_Copy_Tree
(Name
(N
));
2090 if Nkind
(Aggr
) = N_Qualified_Expression
then
2091 Aggr
:= Expression
(Aggr
);
2094 Insert_Actions_After
(N
,
2095 Late_Expansion
(Aggr
, Typ
, Occ
,
2096 Find_Final_List
(Typ
, New_Copy_Tree
(Occ
))));
2097 end Convert_Aggr_In_Assignment
;
2099 ---------------------------------
2100 -- Convert_Aggr_In_Object_Decl --
2101 ---------------------------------
2103 procedure Convert_Aggr_In_Object_Decl
(N
: Node_Id
) is
2104 Obj
: constant Entity_Id
:= Defining_Identifier
(N
);
2105 Aggr
: Node_Id
:= Expression
(N
);
2106 Loc
: constant Source_Ptr
:= Sloc
(Aggr
);
2107 Typ
: constant Entity_Id
:= Etype
(Aggr
);
2108 Occ
: constant Node_Id
:= New_Occurrence_Of
(Obj
, Loc
);
2111 Set_Assignment_OK
(Occ
);
2113 if Nkind
(Aggr
) = N_Qualified_Expression
then
2114 Aggr
:= Expression
(Aggr
);
2117 Insert_Actions_After
(N
, Late_Expansion
(Aggr
, Typ
, Occ
, Obj
=> Obj
));
2118 Set_No_Initialization
(N
);
2119 Initialize_Discriminants
(N
, Typ
);
2120 end Convert_Aggr_In_Object_Decl
;
2122 ----------------------------
2123 -- Convert_To_Assignments --
2124 ----------------------------
2126 procedure Convert_To_Assignments
(N
: Node_Id
; Typ
: Entity_Id
) is
2127 Loc
: constant Source_Ptr
:= Sloc
(N
);
2131 Target_Expr
: Node_Id
;
2132 Parent_Kind
: Node_Kind
;
2133 Unc_Decl
: Boolean := False;
2134 Parent_Node
: Node_Id
;
2138 Parent_Node
:= Parent
(N
);
2139 Parent_Kind
:= Nkind
(Parent_Node
);
2141 if Parent_Kind
= N_Qualified_Expression
then
2143 -- Check if we are in a unconstrained declaration because in this
2144 -- case the current delayed expansion mechanism doesn't work when
2145 -- the declared object size depend on the initializing expr.
2148 Parent_Node
:= Parent
(Parent_Node
);
2149 Parent_Kind
:= Nkind
(Parent_Node
);
2150 if Parent_Kind
= N_Object_Declaration
then
2152 not Is_Entity_Name
(Object_Definition
(Parent_Node
))
2153 or else Has_Discriminants
(
2154 Entity
(Object_Definition
(Parent_Node
)))
2155 or else Is_Class_Wide_Type
(
2156 Entity
(Object_Definition
(Parent_Node
)));
2161 -- Just set the Delay flag in the following cases where the
2162 -- transformation will be done top down from above
2163 -- - internal aggregate (transformed when expanding the parent)
2164 -- - allocators (see Convert_Aggr_In_Allocator)
2165 -- - object decl (see Convert_Aggr_In_Object_Decl)
2166 -- - safe assignments (see Convert_Aggr_Assignments)
2167 -- so far only the assignments in the init_procs are taken
2170 if Parent_Kind
= N_Aggregate
2171 or else Parent_Kind
= N_Extension_Aggregate
2172 or else Parent_Kind
= N_Component_Association
2173 or else Parent_Kind
= N_Allocator
2174 or else (Parent_Kind
= N_Object_Declaration
and then not Unc_Decl
)
2175 or else (Parent_Kind
= N_Assignment_Statement
2176 and then Inside_Init_Proc
)
2178 Set_Expansion_Delayed
(N
);
2182 if Requires_Transient_Scope
(Typ
) then
2183 Establish_Transient_Scope
(N
, Sec_Stack
=>
2184 Is_Controlled
(Typ
) or else Has_Controlled_Component
(Typ
));
2187 -- Create the temporary
2189 Temp
:= Make_Defining_Identifier
(Loc
, New_Internal_Name
('A'));
2192 Make_Object_Declaration
(Loc
,
2193 Defining_Identifier
=> Temp
,
2194 Object_Definition
=> New_Occurrence_Of
(Typ
, Loc
));
2196 Set_No_Initialization
(Instr
);
2197 Insert_Action
(N
, Instr
);
2198 Initialize_Discriminants
(Instr
, Typ
);
2199 Target_Expr
:= New_Occurrence_Of
(Temp
, Loc
);
2201 Insert_Actions
(N
, Build_Record_Aggr_Code
(N
, Typ
, Target_Expr
));
2202 Rewrite
(N
, New_Occurrence_Of
(Temp
, Loc
));
2203 Analyze_And_Resolve
(N
, Typ
);
2204 end Convert_To_Assignments
;
2206 ---------------------------
2207 -- Convert_To_Positional --
2208 ---------------------------
2210 procedure Convert_To_Positional
2212 Max_Others_Replicate
: Nat
:= 5;
2213 Handle_Bit_Packed
: Boolean := False)
2215 Loc
: constant Source_Ptr
:= Sloc
(N
);
2216 Typ
: constant Entity_Id
:= Etype
(N
);
2217 Ndim
: constant Pos
:= Number_Dimensions
(Typ
);
2218 Xtyp
: constant Entity_Id
:= Etype
(First_Index
(Typ
));
2219 Indx
: constant Node_Id
:= First_Index
(Base_Type
(Typ
));
2220 Blo
: constant Node_Id
:= Type_Low_Bound
(Etype
(Indx
));
2221 Lo
: constant Node_Id
:= Type_Low_Bound
(Xtyp
);
2222 Hi
: constant Node_Id
:= Type_High_Bound
(Xtyp
);
2226 -- The following constant determines the maximum size of an
2227 -- aggregate produced by converting named to positional
2228 -- notation (e.g. from others clauses). This avoids running
2229 -- away with attempts to convert huge aggregates.
2231 -- The normal limit is 5000, but we increase this limit to
2232 -- 2**24 (about 16 million) if Restrictions (No_Elaboration_Code)
2233 -- or Restrictions (No_Implicit_Loops) is specified, since in
2234 -- either case, we are at risk of declaring the program illegal
2235 -- because of this limit.
2237 Max_Aggr_Size
: constant Nat
:=
2238 5000 + (2 ** 24 - 5000) * Boolean'Pos
2239 (Restrictions
(No_Elaboration_Code
)
2241 Restrictions
(No_Implicit_Loops
));
2244 -- For now, we only handle the one dimensional case and aggregates
2245 -- that are not part of a component_association
2247 if Ndim
> 1 or else Nkind
(Parent
(N
)) = N_Aggregate
2248 or else Nkind
(Parent
(N
)) = N_Component_Association
2253 -- If already positional, nothing to do!
2255 if No
(Component_Associations
(N
)) then
2259 -- Bounds need to be known at compile time
2261 if not Compile_Time_Known_Value
(Lo
)
2262 or else not Compile_Time_Known_Value
(Hi
)
2267 -- Normally we do not attempt to convert bit packed arrays. The
2268 -- exception is when we are explicitly asked to do so (this call
2269 -- is from the Packed_Array_Aggregate_Handled procedure).
2271 if Is_Bit_Packed_Array
(Typ
)
2272 and then not Handle_Bit_Packed
2277 -- Do not convert to positional if controlled components are
2278 -- involved since these require special processing
2280 if Has_Controlled_Component
(Typ
) then
2284 -- Get bounds and check reasonable size (positive, not too large)
2285 -- Also only handle bounds starting at the base type low bound for now
2286 -- since the compiler isn't able to handle different low bounds yet.
2288 Lov
:= Expr_Value
(Lo
);
2289 Hiv
:= Expr_Value
(Hi
);
2292 or else (Hiv
- Lov
> Max_Aggr_Size
)
2293 or else not Compile_Time_Known_Value
(Blo
)
2294 or else (Lov
/= Expr_Value
(Blo
))
2299 -- Bounds must be in integer range (for array Vals below)
2301 if not UI_Is_In_Int_Range
(Lov
)
2303 not UI_Is_In_Int_Range
(Hiv
)
2308 -- Determine if set of alternatives is suitable for conversion
2309 -- and build an array containing the values in sequence.
2312 Vals
: array (UI_To_Int
(Lov
) .. UI_To_Int
(Hiv
))
2313 of Node_Id
:= (others => Empty
);
2314 -- The values in the aggregate sorted appropriately
2317 -- Same data as Vals in list form
2320 -- Used to validate Max_Others_Replicate limit
2323 Num
: Int
:= UI_To_Int
(Lov
);
2328 if Present
(Expressions
(N
)) then
2329 Elmt
:= First
(Expressions
(N
));
2330 while Present
(Elmt
) loop
2331 Vals
(Num
) := Relocate_Node
(Elmt
);
2337 Elmt
:= First
(Component_Associations
(N
));
2338 Component_Loop
: while Present
(Elmt
) loop
2340 Choice
:= First
(Choices
(Elmt
));
2341 Choice_Loop
: while Present
(Choice
) loop
2343 -- If we have an others choice, fill in the missing elements
2344 -- subject to the limit established by Max_Others_Replicate.
2346 if Nkind
(Choice
) = N_Others_Choice
then
2349 for J
in Vals
'Range loop
2350 if No
(Vals
(J
)) then
2351 Vals
(J
) := New_Copy_Tree
(Expression
(Elmt
));
2352 Rep_Count
:= Rep_Count
+ 1;
2354 -- Check for maximum others replication. Note that
2355 -- we skip this test if either of the restrictions
2356 -- No_Elaboration_Code or No_Implicit_Loops is
2357 -- active, or if this is a preelaborable unit.
2359 if Rep_Count
> Max_Others_Replicate
2360 and then not Restrictions
(No_Elaboration_Code
)
2361 and then not Restrictions
(No_Implicit_Loops
)
2363 Is_Preelaborated
(Cunit_Entity
(Current_Sem_Unit
))
2370 exit Component_Loop
;
2372 -- Case of a subtype mark
2374 elsif (Nkind
(Choice
) = N_Identifier
2375 and then Is_Type
(Entity
(Choice
)))
2377 Lo
:= Type_Low_Bound
(Etype
(Choice
));
2378 Hi
:= Type_High_Bound
(Etype
(Choice
));
2380 -- Case of subtype indication
2382 elsif Nkind
(Choice
) = N_Subtype_Indication
then
2383 Lo
:= Low_Bound
(Range_Expression
(Constraint
(Choice
)));
2384 Hi
:= High_Bound
(Range_Expression
(Constraint
(Choice
)));
2388 elsif Nkind
(Choice
) = N_Range
then
2389 Lo
:= Low_Bound
(Choice
);
2390 Hi
:= High_Bound
(Choice
);
2392 -- Normal subexpression case
2394 else pragma Assert
(Nkind
(Choice
) in N_Subexpr
);
2395 if not Compile_Time_Known_Value
(Choice
) then
2399 Vals
(UI_To_Int
(Expr_Value
(Choice
))) :=
2400 New_Copy_Tree
(Expression
(Elmt
));
2405 -- Range cases merge with Lo,Hi said
2407 if not Compile_Time_Known_Value
(Lo
)
2409 not Compile_Time_Known_Value
(Hi
)
2413 for J
in UI_To_Int
(Expr_Value
(Lo
)) ..
2414 UI_To_Int
(Expr_Value
(Hi
))
2416 Vals
(J
) := New_Copy_Tree
(Expression
(Elmt
));
2422 end loop Choice_Loop
;
2425 end loop Component_Loop
;
2427 -- If we get here the conversion is possible
2430 for J
in Vals
'Range loop
2431 Append
(Vals
(J
), Vlist
);
2434 Rewrite
(N
, Make_Aggregate
(Loc
, Expressions
=> Vlist
));
2435 Analyze_And_Resolve
(N
, Typ
);
2437 end Convert_To_Positional
;
2439 ----------------------------
2440 -- Expand_Array_Aggregate --
2441 ----------------------------
2443 -- Array aggregate expansion proceeds as follows:
2445 -- 1. If requested we generate code to perform all the array aggregate
2446 -- bound checks, specifically
2448 -- (a) Check that the index range defined by aggregate bounds is
2449 -- compatible with corresponding index subtype.
2451 -- (b) If an others choice is present check that no aggregate
2452 -- index is outside the bounds of the index constraint.
2454 -- (c) For multidimensional arrays make sure that all subaggregates
2455 -- corresponding to the same dimension have the same bounds.
2457 -- 2. Check if the aggregate can be statically processed. If this is the
2458 -- case pass it as is to Gigi. Note that a necessary condition for
2459 -- static processing is that the aggregate be fully positional.
2461 -- 3. If in place aggregate expansion is possible (i.e. no need to create
2462 -- a temporary) then mark the aggregate as such and return. Otherwise
2463 -- create a new temporary and generate the appropriate initialization
2466 procedure Expand_Array_Aggregate
(N
: Node_Id
) is
2467 Loc
: constant Source_Ptr
:= Sloc
(N
);
2469 Typ
: constant Entity_Id
:= Etype
(N
);
2470 Ctyp
: constant Entity_Id
:= Component_Type
(Typ
);
2471 -- Typ is the correct constrained array subtype of the aggregate
2472 -- Ctyp is the corresponding component type.
2474 Aggr_Dimension
: constant Pos
:= Number_Dimensions
(Typ
);
2475 -- Number of aggregate index dimensions.
2477 Aggr_Low
: array (1 .. Aggr_Dimension
) of Node_Id
;
2478 Aggr_High
: array (1 .. Aggr_Dimension
) of Node_Id
;
2479 -- Low and High bounds of the constraint for each aggregate index.
2481 Aggr_Index_Typ
: array (1 .. Aggr_Dimension
) of Entity_Id
;
2482 -- The type of each index.
2484 Maybe_In_Place_OK
: Boolean;
2485 -- If the type is neither controlled nor packed and the aggregate
2486 -- is the expression in an assignment, assignment in place may be
2487 -- possible, provided other conditions are met on the LHS.
2489 Others_Present
: array (1 .. Aggr_Dimension
) of Boolean :=
2491 -- If Others_Present (J) is True, then there is an others choice
2492 -- in one of the sub-aggregates of N at dimension J.
2494 procedure Build_Constrained_Type
(Positional
: Boolean);
2495 -- If the subtype is not static or unconstrained, build a constrained
2496 -- type using the computable sizes of the aggregate and its sub-
2499 procedure Check_Bounds
(Aggr_Bounds
: Node_Id
; Index_Bounds
: Node_Id
);
2500 -- Checks that the bounds of Aggr_Bounds are within the bounds defined
2503 procedure Check_Same_Aggr_Bounds
(Sub_Aggr
: Node_Id
; Dim
: Pos
);
2504 -- Checks that in a multi-dimensional array aggregate all subaggregates
2505 -- corresponding to the same dimension have the same bounds.
2506 -- Sub_Aggr is an array sub-aggregate. Dim is the dimension
2507 -- corresponding to the sub-aggregate.
2509 procedure Compute_Others_Present
(Sub_Aggr
: Node_Id
; Dim
: Pos
);
2510 -- Computes the values of array Others_Present. Sub_Aggr is the
2511 -- array sub-aggregate we start the computation from. Dim is the
2512 -- dimension corresponding to the sub-aggregate.
2514 function Has_Address_Clause
(D
: Node_Id
) return Boolean;
2515 -- If the aggregate is the expression in an object declaration, it
2516 -- cannot be expanded in place. This function does a lookahead in the
2517 -- current declarative part to find an address clause for the object
2520 function In_Place_Assign_OK
return Boolean;
2521 -- Simple predicate to determine whether an aggregate assignment can
2522 -- be done in place, because none of the new values can depend on the
2523 -- components of the target of the assignment.
2525 procedure Others_Check
(Sub_Aggr
: Node_Id
; Dim
: Pos
);
2526 -- Checks that if an others choice is present in any sub-aggregate no
2527 -- aggregate index is outside the bounds of the index constraint.
2528 -- Sub_Aggr is an array sub-aggregate. Dim is the dimension
2529 -- corresponding to the sub-aggregate.
2531 ----------------------------
2532 -- Build_Constrained_Type --
2533 ----------------------------
2535 procedure Build_Constrained_Type
(Positional
: Boolean) is
2536 Loc
: constant Source_Ptr
:= Sloc
(N
);
2537 Agg_Type
: Entity_Id
;
2540 Typ
: constant Entity_Id
:= Etype
(N
);
2541 Indices
: List_Id
:= New_List
;
2547 Make_Defining_Identifier
(
2548 Loc
, New_Internal_Name
('A'));
2550 -- If the aggregate is purely positional, all its subaggregates
2551 -- have the same size. We collect the dimensions from the first
2552 -- subaggregate at each level.
2557 for D
in 1 .. Number_Dimensions
(Typ
) loop
2558 Comp
:= First
(Expressions
(Sub_Agg
));
2563 while Present
(Comp
) loop
2570 Low_Bound
=> Make_Integer_Literal
(Loc
, 1),
2572 Make_Integer_Literal
(Loc
, Num
)),
2578 -- We know the aggregate type is unconstrained and the
2579 -- aggregate is not processable by the back end, therefore
2580 -- not necessarily positional. Retrieve the bounds of each
2581 -- dimension as computed earlier.
2583 for D
in 1 .. Number_Dimensions
(Typ
) loop
2586 Low_Bound
=> Aggr_Low
(D
),
2587 High_Bound
=> Aggr_High
(D
)),
2593 Make_Full_Type_Declaration
(Loc
,
2594 Defining_Identifier
=> Agg_Type
,
2596 Make_Constrained_Array_Definition
(Loc
,
2597 Discrete_Subtype_Definitions
=> Indices
,
2598 Subtype_Indication
=>
2599 New_Occurrence_Of
(Component_Type
(Typ
), Loc
)));
2601 Insert_Action
(N
, Decl
);
2603 Set_Etype
(N
, Agg_Type
);
2604 Set_Is_Itype
(Agg_Type
);
2605 Freeze_Itype
(Agg_Type
, N
);
2606 end Build_Constrained_Type
;
2612 procedure Check_Bounds
(Aggr_Bounds
: Node_Id
; Index_Bounds
: Node_Id
) is
2619 Cond
: Node_Id
:= Empty
;
2622 Get_Index_Bounds
(Aggr_Bounds
, Aggr_Lo
, Aggr_Hi
);
2623 Get_Index_Bounds
(Index_Bounds
, Ind_Lo
, Ind_Hi
);
2625 -- Generate the following test:
2627 -- [constraint_error when
2628 -- Aggr_Lo <= Aggr_Hi and then
2629 -- (Aggr_Lo < Ind_Lo or else Aggr_Hi > Ind_Hi)]
2631 -- As an optimization try to see if some tests are trivially vacuos
2632 -- because we are comparing an expression against itself.
2634 if Aggr_Lo
= Ind_Lo
and then Aggr_Hi
= Ind_Hi
then
2637 elsif Aggr_Hi
= Ind_Hi
then
2640 Left_Opnd
=> Duplicate_Subexpr
(Aggr_Lo
),
2641 Right_Opnd
=> Duplicate_Subexpr
(Ind_Lo
));
2643 elsif Aggr_Lo
= Ind_Lo
then
2646 Left_Opnd
=> Duplicate_Subexpr
(Aggr_Hi
),
2647 Right_Opnd
=> Duplicate_Subexpr
(Ind_Hi
));
2654 Left_Opnd
=> Duplicate_Subexpr
(Aggr_Lo
),
2655 Right_Opnd
=> Duplicate_Subexpr
(Ind_Lo
)),
2659 Left_Opnd
=> Duplicate_Subexpr
(Aggr_Hi
),
2660 Right_Opnd
=> Duplicate_Subexpr
(Ind_Hi
)));
2663 if Present
(Cond
) then
2668 Left_Opnd
=> Duplicate_Subexpr
(Aggr_Lo
),
2669 Right_Opnd
=> Duplicate_Subexpr
(Aggr_Hi
)),
2671 Right_Opnd
=> Cond
);
2673 Set_Analyzed
(Left_Opnd
(Left_Opnd
(Cond
)), False);
2674 Set_Analyzed
(Right_Opnd
(Left_Opnd
(Cond
)), False);
2676 Make_Raise_Constraint_Error
(Loc
,
2678 Reason
=> CE_Length_Check_Failed
));
2682 ----------------------------
2683 -- Check_Same_Aggr_Bounds --
2684 ----------------------------
2686 procedure Check_Same_Aggr_Bounds
(Sub_Aggr
: Node_Id
; Dim
: Pos
) is
2687 Sub_Lo
: constant Node_Id
:= Low_Bound
(Aggregate_Bounds
(Sub_Aggr
));
2688 Sub_Hi
: constant Node_Id
:= High_Bound
(Aggregate_Bounds
(Sub_Aggr
));
2689 -- The bounds of this specific sub-aggregate.
2691 Aggr_Lo
: constant Node_Id
:= Aggr_Low
(Dim
);
2692 Aggr_Hi
: constant Node_Id
:= Aggr_High
(Dim
);
2693 -- The bounds of the aggregate for this dimension
2695 Ind_Typ
: constant Entity_Id
:= Aggr_Index_Typ
(Dim
);
2696 -- The index type for this dimension.
2698 Cond
: Node_Id
:= Empty
;
2704 -- If index checks are on generate the test
2706 -- [constraint_error when
2707 -- Aggr_Lo /= Sub_Lo or else Aggr_Hi /= Sub_Hi]
2709 -- As an optimization try to see if some tests are trivially vacuos
2710 -- because we are comparing an expression against itself. Also for
2711 -- the first dimension the test is trivially vacuous because there
2712 -- is just one aggregate for dimension 1.
2714 if Index_Checks_Suppressed
(Ind_Typ
) then
2718 or else (Aggr_Lo
= Sub_Lo
and then Aggr_Hi
= Sub_Hi
)
2722 elsif Aggr_Hi
= Sub_Hi
then
2725 Left_Opnd
=> Duplicate_Subexpr
(Aggr_Lo
),
2726 Right_Opnd
=> Duplicate_Subexpr
(Sub_Lo
));
2728 elsif Aggr_Lo
= Sub_Lo
then
2731 Left_Opnd
=> Duplicate_Subexpr
(Aggr_Hi
),
2732 Right_Opnd
=> Duplicate_Subexpr
(Sub_Hi
));
2739 Left_Opnd
=> Duplicate_Subexpr
(Aggr_Lo
),
2740 Right_Opnd
=> Duplicate_Subexpr
(Sub_Lo
)),
2744 Left_Opnd
=> Duplicate_Subexpr
(Aggr_Hi
),
2745 Right_Opnd
=> Duplicate_Subexpr
(Sub_Hi
)));
2748 if Present
(Cond
) then
2750 Make_Raise_Constraint_Error
(Loc
,
2752 Reason
=> CE_Length_Check_Failed
));
2755 -- Now look inside the sub-aggregate to see if there is more work
2757 if Dim
< Aggr_Dimension
then
2759 -- Process positional components
2761 if Present
(Expressions
(Sub_Aggr
)) then
2762 Expr
:= First
(Expressions
(Sub_Aggr
));
2763 while Present
(Expr
) loop
2764 Check_Same_Aggr_Bounds
(Expr
, Dim
+ 1);
2769 -- Process component associations
2771 if Present
(Component_Associations
(Sub_Aggr
)) then
2772 Assoc
:= First
(Component_Associations
(Sub_Aggr
));
2773 while Present
(Assoc
) loop
2774 Expr
:= Expression
(Assoc
);
2775 Check_Same_Aggr_Bounds
(Expr
, Dim
+ 1);
2780 end Check_Same_Aggr_Bounds
;
2782 ----------------------------
2783 -- Compute_Others_Present --
2784 ----------------------------
2786 procedure Compute_Others_Present
(Sub_Aggr
: Node_Id
; Dim
: Pos
) is
2791 if Present
(Component_Associations
(Sub_Aggr
)) then
2792 Assoc
:= Last
(Component_Associations
(Sub_Aggr
));
2794 if Nkind
(First
(Choices
(Assoc
))) = N_Others_Choice
then
2795 Others_Present
(Dim
) := True;
2799 -- Now look inside the sub-aggregate to see if there is more work
2801 if Dim
< Aggr_Dimension
then
2803 -- Process positional components
2805 if Present
(Expressions
(Sub_Aggr
)) then
2806 Expr
:= First
(Expressions
(Sub_Aggr
));
2807 while Present
(Expr
) loop
2808 Compute_Others_Present
(Expr
, Dim
+ 1);
2813 -- Process component associations
2815 if Present
(Component_Associations
(Sub_Aggr
)) then
2816 Assoc
:= First
(Component_Associations
(Sub_Aggr
));
2817 while Present
(Assoc
) loop
2818 Expr
:= Expression
(Assoc
);
2819 Compute_Others_Present
(Expr
, Dim
+ 1);
2824 end Compute_Others_Present
;
2826 -------------------------
2827 -- Has_Address_Clause --
2828 -------------------------
2830 function Has_Address_Clause
(D
: Node_Id
) return Boolean is
2831 Id
: Entity_Id
:= Defining_Identifier
(D
);
2832 Decl
: Node_Id
:= Next
(D
);
2835 while Present
(Decl
) loop
2837 if Nkind
(Decl
) = N_At_Clause
2838 and then Chars
(Identifier
(Decl
)) = Chars
(Id
)
2842 elsif Nkind
(Decl
) = N_Attribute_Definition_Clause
2843 and then Chars
(Decl
) = Name_Address
2844 and then Chars
(Name
(Decl
)) = Chars
(Id
)
2853 end Has_Address_Clause
;
2855 ------------------------
2856 -- In_Place_Assign_OK --
2857 ------------------------
2859 function In_Place_Assign_OK
return Boolean is
2867 function Is_Others_Aggregate
(Aggr
: Node_Id
) return Boolean;
2868 -- Aggregates that consist of a single Others choice are safe
2869 -- if the single expression is.
2871 function Safe_Aggregate
(Aggr
: Node_Id
) return Boolean;
2872 -- Check recursively that each component of a (sub)aggregate does
2873 -- not depend on the variable being assigned to.
2875 function Safe_Component
(Expr
: Node_Id
) return Boolean;
2876 -- Verify that an expression cannot depend on the variable being
2877 -- assigned to. Room for improvement here (but less than before).
2879 -------------------------
2880 -- Is_Others_Aggregate --
2881 -------------------------
2883 function Is_Others_Aggregate
(Aggr
: Node_Id
) return Boolean is
2885 return No
(Expressions
(Aggr
))
2887 (First
(Choices
(First
(Component_Associations
(Aggr
)))))
2889 end Is_Others_Aggregate
;
2891 --------------------
2892 -- Safe_Aggregate --
2893 --------------------
2895 function Safe_Aggregate
(Aggr
: Node_Id
) return Boolean is
2899 if Present
(Expressions
(Aggr
)) then
2900 Expr
:= First
(Expressions
(Aggr
));
2902 while Present
(Expr
) loop
2903 if Nkind
(Expr
) = N_Aggregate
then
2904 if not Safe_Aggregate
(Expr
) then
2908 elsif not Safe_Component
(Expr
) then
2916 if Present
(Component_Associations
(Aggr
)) then
2917 Expr
:= First
(Component_Associations
(Aggr
));
2919 while Present
(Expr
) loop
2920 if Nkind
(Expression
(Expr
)) = N_Aggregate
then
2921 if not Safe_Aggregate
(Expression
(Expr
)) then
2925 elsif not Safe_Component
(Expression
(Expr
)) then
2936 --------------------
2937 -- Safe_Component --
2938 --------------------
2940 function Safe_Component
(Expr
: Node_Id
) return Boolean is
2941 Comp
: Node_Id
:= Expr
;
2943 function Check_Component
(Comp
: Node_Id
) return Boolean;
2944 -- Do the recursive traversal, after copy.
2946 function Check_Component
(Comp
: Node_Id
) return Boolean is
2948 if Is_Overloaded
(Comp
) then
2952 return Compile_Time_Known_Value
(Comp
)
2954 or else (Is_Entity_Name
(Comp
)
2955 and then Present
(Entity
(Comp
))
2956 and then No
(Renamed_Object
(Entity
(Comp
))))
2958 or else (Nkind
(Comp
) = N_Attribute_Reference
2959 and then Check_Component
(Prefix
(Comp
)))
2961 or else (Nkind
(Comp
) in N_Binary_Op
2962 and then Check_Component
(Left_Opnd
(Comp
))
2963 and then Check_Component
(Right_Opnd
(Comp
)))
2965 or else (Nkind
(Comp
) in N_Unary_Op
2966 and then Check_Component
(Right_Opnd
(Comp
)))
2968 or else (Nkind
(Comp
) = N_Selected_Component
2969 and then Check_Component
(Prefix
(Comp
)));
2970 end Check_Component
;
2972 -- Start of processing for Safe_Component
2975 -- If the component appears in an association that may
2976 -- correspond to more than one element, it is not analyzed
2977 -- before the expansion into assignments, to avoid side effects.
2978 -- We analyze, but do not resolve the copy, to obtain sufficient
2979 -- entity information for the checks that follow. If component is
2980 -- overloaded we assume an unsafe function call.
2982 if not Analyzed
(Comp
) then
2983 if Is_Overloaded
(Expr
) then
2986 elsif Nkind
(Expr
) = N_Aggregate
2987 and then not Is_Others_Aggregate
(Expr
)
2991 elsif Nkind
(Expr
) = N_Allocator
then
2992 -- For now, too complex to analyze.
2997 Comp
:= New_Copy_Tree
(Expr
);
2998 Set_Parent
(Comp
, Parent
(Expr
));
3002 if Nkind
(Comp
) = N_Aggregate
then
3003 return Safe_Aggregate
(Comp
);
3005 return Check_Component
(Comp
);
3009 -- Start of processing for In_Place_Assign_OK
3012 if Present
(Component_Associations
(N
)) then
3014 -- On assignment, sliding can take place, so we cannot do the
3015 -- assignment in place unless the bounds of the aggregate are
3016 -- statically equal to those of the target.
3018 -- If the aggregate is given by an others choice, the bounds
3019 -- are derived from the left-hand side, and the assignment is
3020 -- safe if the expression is.
3022 if Is_Others_Aggregate
(N
) then
3025 (Expression
(First
(Component_Associations
(N
))));
3028 Aggr_In
:= First_Index
(Etype
(N
));
3029 Obj_In
:= First_Index
(Etype
(Name
(Parent
(N
))));
3031 while Present
(Aggr_In
) loop
3032 Get_Index_Bounds
(Aggr_In
, Aggr_Lo
, Aggr_Hi
);
3033 Get_Index_Bounds
(Obj_In
, Obj_Lo
, Obj_Hi
);
3035 if not Compile_Time_Known_Value
(Aggr_Lo
)
3036 or else not Compile_Time_Known_Value
(Aggr_Hi
)
3037 or else not Compile_Time_Known_Value
(Obj_Lo
)
3038 or else not Compile_Time_Known_Value
(Obj_Hi
)
3039 or else Expr_Value
(Aggr_Lo
) /= Expr_Value
(Obj_Lo
)
3040 or else Expr_Value
(Aggr_Hi
) /= Expr_Value
(Obj_Hi
)
3045 Next_Index
(Aggr_In
);
3046 Next_Index
(Obj_In
);
3050 -- Now check the component values themselves.
3052 return Safe_Aggregate
(N
);
3053 end In_Place_Assign_OK
;
3059 procedure Others_Check
(Sub_Aggr
: Node_Id
; Dim
: Pos
) is
3060 Aggr_Lo
: constant Node_Id
:= Aggr_Low
(Dim
);
3061 Aggr_Hi
: constant Node_Id
:= Aggr_High
(Dim
);
3062 -- The bounds of the aggregate for this dimension.
3064 Ind_Typ
: constant Entity_Id
:= Aggr_Index_Typ
(Dim
);
3065 -- The index type for this dimension.
3067 Need_To_Check
: Boolean := False;
3069 Choices_Lo
: Node_Id
:= Empty
;
3070 Choices_Hi
: Node_Id
:= Empty
;
3071 -- The lowest and highest discrete choices for a named sub-aggregate
3073 Nb_Choices
: Int
:= -1;
3074 -- The number of discrete non-others choices in this sub-aggregate
3076 Nb_Elements
: Uint
:= Uint_0
;
3077 -- The number of elements in a positional aggregate
3079 Cond
: Node_Id
:= Empty
;
3086 -- Check if we have an others choice. If we do make sure that this
3087 -- sub-aggregate contains at least one element in addition to the
3090 if Range_Checks_Suppressed
(Ind_Typ
) then
3091 Need_To_Check
:= False;
3093 elsif Present
(Expressions
(Sub_Aggr
))
3094 and then Present
(Component_Associations
(Sub_Aggr
))
3096 Need_To_Check
:= True;
3098 elsif Present
(Component_Associations
(Sub_Aggr
)) then
3099 Assoc
:= Last
(Component_Associations
(Sub_Aggr
));
3101 if Nkind
(First
(Choices
(Assoc
))) /= N_Others_Choice
then
3102 Need_To_Check
:= False;
3105 -- Count the number of discrete choices. Start with -1
3106 -- because the others choice does not count.
3109 Assoc
:= First
(Component_Associations
(Sub_Aggr
));
3110 while Present
(Assoc
) loop
3111 Choice
:= First
(Choices
(Assoc
));
3112 while Present
(Choice
) loop
3113 Nb_Choices
:= Nb_Choices
+ 1;
3120 -- If there is only an others choice nothing to do
3122 Need_To_Check
:= (Nb_Choices
> 0);
3126 Need_To_Check
:= False;
3129 -- If we are dealing with a positional sub-aggregate with an
3130 -- others choice then compute the number or positional elements.
3132 if Need_To_Check
and then Present
(Expressions
(Sub_Aggr
)) then
3133 Expr
:= First
(Expressions
(Sub_Aggr
));
3134 Nb_Elements
:= Uint_0
;
3135 while Present
(Expr
) loop
3136 Nb_Elements
:= Nb_Elements
+ 1;
3140 -- If the aggregate contains discrete choices and an others choice
3141 -- compute the smallest and largest discrete choice values.
3143 elsif Need_To_Check
then
3144 Compute_Choices_Lo_And_Choices_Hi
: declare
3146 Table
: Case_Table_Type
(1 .. Nb_Choices
);
3147 -- Used to sort all the different choice values
3154 Assoc
:= First
(Component_Associations
(Sub_Aggr
));
3155 while Present
(Assoc
) loop
3156 Choice
:= First
(Choices
(Assoc
));
3157 while Present
(Choice
) loop
3158 if Nkind
(Choice
) = N_Others_Choice
then
3162 Get_Index_Bounds
(Choice
, Low
, High
);
3163 Table
(J
).Choice_Lo
:= Low
;
3164 Table
(J
).Choice_Hi
:= High
;
3173 -- Sort the discrete choices
3175 Sort_Case_Table
(Table
);
3177 Choices_Lo
:= Table
(1).Choice_Lo
;
3178 Choices_Hi
:= Table
(Nb_Choices
).Choice_Hi
;
3179 end Compute_Choices_Lo_And_Choices_Hi
;
3182 -- If no others choice in this sub-aggregate, or the aggregate
3183 -- comprises only an others choice, nothing to do.
3185 if not Need_To_Check
then
3188 -- If we are dealing with an aggregate containing an others
3189 -- choice and positional components, we generate the following test:
3191 -- if Ind_Typ'Pos (Aggr_Lo) + (Nb_Elements - 1) >
3192 -- Ind_Typ'Pos (Aggr_Hi)
3194 -- raise Constraint_Error;
3197 elsif Nb_Elements
> Uint_0
then
3203 Make_Attribute_Reference
(Loc
,
3204 Prefix
=> New_Reference_To
(Ind_Typ
, Loc
),
3205 Attribute_Name
=> Name_Pos
,
3207 New_List
(Duplicate_Subexpr
(Aggr_Lo
))),
3208 Right_Opnd
=> Make_Integer_Literal
(Loc
, Nb_Elements
- 1)),
3211 Make_Attribute_Reference
(Loc
,
3212 Prefix
=> New_Reference_To
(Ind_Typ
, Loc
),
3213 Attribute_Name
=> Name_Pos
,
3214 Expressions
=> New_List
(Duplicate_Subexpr
(Aggr_Hi
))));
3216 -- If we are dealing with an aggregate containing an others
3217 -- choice and discrete choices we generate the following test:
3219 -- [constraint_error when
3220 -- Choices_Lo < Aggr_Lo or else Choices_Hi > Aggr_Hi];
3227 Left_Opnd
=> Duplicate_Subexpr
(Choices_Lo
),
3228 Right_Opnd
=> Duplicate_Subexpr
(Aggr_Lo
)),
3232 Left_Opnd
=> Duplicate_Subexpr
(Choices_Hi
),
3233 Right_Opnd
=> Duplicate_Subexpr
(Aggr_Hi
)));
3236 if Present
(Cond
) then
3238 Make_Raise_Constraint_Error
(Loc
,
3240 Reason
=> CE_Length_Check_Failed
));
3243 -- Now look inside the sub-aggregate to see if there is more work
3245 if Dim
< Aggr_Dimension
then
3247 -- Process positional components
3249 if Present
(Expressions
(Sub_Aggr
)) then
3250 Expr
:= First
(Expressions
(Sub_Aggr
));
3251 while Present
(Expr
) loop
3252 Others_Check
(Expr
, Dim
+ 1);
3257 -- Process component associations
3259 if Present
(Component_Associations
(Sub_Aggr
)) then
3260 Assoc
:= First
(Component_Associations
(Sub_Aggr
));
3261 while Present
(Assoc
) loop
3262 Expr
:= Expression
(Assoc
);
3263 Others_Check
(Expr
, Dim
+ 1);
3270 -- Remaining Expand_Array_Aggregate variables
3273 -- Holds the temporary aggregate value.
3276 -- Holds the declaration of Tmp.
3278 Aggr_Code
: List_Id
;
3279 Parent_Node
: Node_Id
;
3280 Parent_Kind
: Node_Kind
;
3282 -- Start of processing for Expand_Array_Aggregate
3285 -- Do not touch the special aggregates of attributes used for Asm calls
3287 if Is_RTE
(Ctyp
, RE_Asm_Input_Operand
)
3288 or else Is_RTE
(Ctyp
, RE_Asm_Output_Operand
)
3293 -- If the semantic analyzer has determined that aggregate N will raise
3294 -- Constraint_Error at run-time, then the aggregate node has been
3295 -- replaced with an N_Raise_Constraint_Error node and we should
3298 pragma Assert
(not Raises_Constraint_Error
(N
));
3300 -- STEP 1: Check (a)
3302 Index_Compatibility_Check
: declare
3303 Aggr_Index_Range
: Node_Id
:= First_Index
(Typ
);
3304 -- The current aggregate index range
3306 Index_Constraint
: Node_Id
:= First_Index
(Etype
(Typ
));
3307 -- The corresponding index constraint against which we have to
3308 -- check the above aggregate index range.
3311 Compute_Others_Present
(N
, 1);
3313 for J
in 1 .. Aggr_Dimension
loop
3314 -- There is no need to emit a check if an others choice is
3315 -- present for this array aggregate dimension since in this
3316 -- case one of N's sub-aggregates has taken its bounds from the
3317 -- context and these bounds must have been checked already. In
3318 -- addition all sub-aggregates corresponding to the same
3319 -- dimension must all have the same bounds (checked in (c) below).
3321 if not Range_Checks_Suppressed
(Etype
(Index_Constraint
))
3322 and then not Others_Present
(J
)
3324 -- We don't use Checks.Apply_Range_Check here because it
3325 -- emits a spurious check. Namely it checks that the range
3326 -- defined by the aggregate bounds is non empty. But we know
3327 -- this already if we get here.
3329 Check_Bounds
(Aggr_Index_Range
, Index_Constraint
);
3332 -- Save the low and high bounds of the aggregate index as well
3333 -- as the index type for later use in checks (b) and (c) below.
3335 Aggr_Low
(J
) := Low_Bound
(Aggr_Index_Range
);
3336 Aggr_High
(J
) := High_Bound
(Aggr_Index_Range
);
3338 Aggr_Index_Typ
(J
) := Etype
(Index_Constraint
);
3340 Next_Index
(Aggr_Index_Range
);
3341 Next_Index
(Index_Constraint
);
3343 end Index_Compatibility_Check
;
3345 -- STEP 1: Check (b)
3347 Others_Check
(N
, 1);
3349 -- STEP 1: Check (c)
3351 if Aggr_Dimension
> 1 then
3352 Check_Same_Aggr_Bounds
(N
, 1);
3357 -- First try to convert to positional form. If the result is not
3358 -- an aggregate any more, then we are done with the analysis (it
3359 -- it could be a string literal or an identifier for a temporary
3360 -- variable following this call). If result is an analyzed aggregate
3361 -- the transformation was also successful and we are done as well.
3363 Convert_To_Positional
(N
);
3365 if Nkind
(N
) /= N_Aggregate
then
3369 and then N
/= Original_Node
(N
)
3374 if Backend_Processing_Possible
(N
) then
3376 -- If the aggregate is static but the constraints are not, build
3377 -- a static subtype for the aggregate, so that Gigi can place it
3378 -- in static memory. Perform an unchecked_conversion to the non-
3379 -- static type imposed by the context.
3382 Itype
: constant Entity_Id
:= Etype
(N
);
3384 Needs_Type
: Boolean := False;
3387 Index
:= First_Index
(Itype
);
3389 while Present
(Index
) loop
3390 if not Is_Static_Subtype
(Etype
(Index
)) then
3399 Build_Constrained_Type
(Positional
=> True);
3400 Rewrite
(N
, Unchecked_Convert_To
(Itype
, N
));
3408 -- Delay expansion for nested aggregates it will be taken care of
3409 -- when the parent aggregate is expanded
3411 Parent_Node
:= Parent
(N
);
3412 Parent_Kind
:= Nkind
(Parent_Node
);
3414 if Parent_Kind
= N_Qualified_Expression
then
3415 Parent_Node
:= Parent
(Parent_Node
);
3416 Parent_Kind
:= Nkind
(Parent_Node
);
3419 if Parent_Kind
= N_Aggregate
3420 or else Parent_Kind
= N_Extension_Aggregate
3421 or else Parent_Kind
= N_Component_Association
3422 or else (Parent_Kind
= N_Object_Declaration
3423 and then Controlled_Type
(Typ
))
3424 or else (Parent_Kind
= N_Assignment_Statement
3425 and then Inside_Init_Proc
)
3427 Set_Expansion_Delayed
(N
);
3433 -- Look if in place aggregate expansion is possible
3435 -- First case to test for is packed array aggregate that we can
3436 -- handle at compile time. If so, return with transformation done.
3438 if Packed_Array_Aggregate_Handled
(N
) then
3442 -- For object declarations we build the aggregate in place, unless
3443 -- the array is bit-packed or the component is controlled.
3445 -- For assignments we do the assignment in place if all the component
3446 -- associations have compile-time known values. For other cases we
3447 -- create a temporary. The analysis for safety of on-line assignment
3448 -- is delicate, i.e. we don't know how to do it fully yet ???
3450 if Requires_Transient_Scope
(Typ
) then
3451 Establish_Transient_Scope
3452 (N
, Sec_Stack
=> Has_Controlled_Component
(Typ
));
3455 Maybe_In_Place_OK
:=
3456 Comes_From_Source
(N
)
3457 and then Nkind
(Parent
(N
)) = N_Assignment_Statement
3458 and then not Is_Bit_Packed_Array
(Typ
)
3459 and then not Has_Controlled_Component
(Typ
)
3460 and then In_Place_Assign_OK
;
3462 if Comes_From_Source
(Parent
(N
))
3463 and then Nkind
(Parent
(N
)) = N_Object_Declaration
3464 and then N
= Expression
(Parent
(N
))
3465 and then not Is_Bit_Packed_Array
(Typ
)
3466 and then not Has_Controlled_Component
(Typ
)
3467 and then not Has_Address_Clause
(Parent
(N
))
3469 Tmp
:= Defining_Identifier
(Parent
(N
));
3470 Set_No_Initialization
(Parent
(N
));
3471 Set_Expression
(Parent
(N
), Empty
);
3473 -- Set the type of the entity, for use in the analysis of the
3474 -- subsequent indexed assignments. If the nominal type is not
3475 -- constrained, build a subtype from the known bounds of the
3476 -- aggregate. If the declaration has a subtype mark, use it,
3477 -- otherwise use the itype of the aggregate.
3479 if not Is_Constrained
(Typ
) then
3480 Build_Constrained_Type
(Positional
=> False);
3481 elsif Is_Entity_Name
(Object_Definition
(Parent
(N
)))
3482 and then Is_Constrained
(Entity
(Object_Definition
(Parent
(N
))))
3484 Set_Etype
(Tmp
, Entity
(Object_Definition
(Parent
(N
))));
3486 Set_Size_Known_At_Compile_Time
(Typ
, False);
3487 Set_Etype
(Tmp
, Typ
);
3490 elsif Maybe_In_Place_OK
3491 and then Is_Entity_Name
(Name
(Parent
(N
)))
3493 Tmp
:= Entity
(Name
(Parent
(N
)));
3495 if Etype
(Tmp
) /= Etype
(N
) then
3496 Apply_Length_Check
(N
, Etype
(Tmp
));
3499 elsif Maybe_In_Place_OK
3500 and then Nkind
(Name
(Parent
(N
))) = N_Explicit_Dereference
3501 and then Is_Entity_Name
(Prefix
(Name
(Parent
(N
))))
3503 Tmp
:= Name
(Parent
(N
));
3505 if Etype
(Tmp
) /= Etype
(N
) then
3506 Apply_Length_Check
(N
, Etype
(Tmp
));
3509 elsif Maybe_In_Place_OK
3510 and then Nkind
(Name
(Parent
(N
))) = N_Slice
3511 and then Safe_Slice_Assignment
(N
)
3513 -- Safe_Slice_Assignment rewrites assignment as a loop
3518 Maybe_In_Place_OK
:= False;
3519 Tmp
:= Make_Defining_Identifier
(Loc
, New_Internal_Name
('A'));
3521 Make_Object_Declaration
3523 Defining_Identifier
=> Tmp
,
3524 Object_Definition
=> New_Occurrence_Of
(Typ
, Loc
));
3525 Set_No_Initialization
(Tmp_Decl
, True);
3527 -- If we are within a loop, the temporary will be pushed on the
3528 -- stack at each iteration. If the aggregate is the expression for
3529 -- an allocator, it will be immediately copied to the heap and can
3530 -- be reclaimed at once. We create a transient scope around the
3531 -- aggregate for this purpose.
3533 if Ekind
(Current_Scope
) = E_Loop
3534 and then Nkind
(Parent
(Parent
(N
))) = N_Allocator
3536 Establish_Transient_Scope
(N
, False);
3539 Insert_Action
(N
, Tmp_Decl
);
3542 -- Construct and insert the aggregate code. We can safely suppress
3543 -- index checks because this code is guaranteed not to raise CE
3544 -- on index checks. However we should *not* suppress all checks.
3550 if Nkind
(Tmp
) = N_Defining_Identifier
then
3551 Target
:= New_Reference_To
(Tmp
, Loc
);
3554 -- Name in assignment is explicit dereference.
3556 Target
:= New_Copy
(Tmp
);
3560 Build_Array_Aggr_Code
(N
,
3561 Index
=> First_Index
(Typ
),
3563 Scalar_Comp
=> Is_Scalar_Type
(Ctyp
));
3566 if Comes_From_Source
(Tmp
) then
3567 Insert_Actions_After
(Parent
(N
), Aggr_Code
);
3570 Insert_Actions
(N
, Aggr_Code
);
3573 -- If the aggregate has been assigned in place, remove the original
3576 if Nkind
(Parent
(N
)) = N_Assignment_Statement
3577 and then Maybe_In_Place_OK
3579 Rewrite
(Parent
(N
), Make_Null_Statement
(Loc
));
3581 elsif Nkind
(Parent
(N
)) /= N_Object_Declaration
3582 or else Tmp
/= Defining_Identifier
(Parent
(N
))
3584 Rewrite
(N
, New_Occurrence_Of
(Tmp
, Loc
));
3585 Analyze_And_Resolve
(N
, Typ
);
3587 end Expand_Array_Aggregate
;
3589 ------------------------
3590 -- Expand_N_Aggregate --
3591 ------------------------
3593 procedure Expand_N_Aggregate
(N
: Node_Id
) is
3595 if Is_Record_Type
(Etype
(N
)) then
3596 Expand_Record_Aggregate
(N
);
3598 Expand_Array_Aggregate
(N
);
3600 end Expand_N_Aggregate
;
3602 ----------------------------------
3603 -- Expand_N_Extension_Aggregate --
3604 ----------------------------------
3606 -- If the ancestor part is an expression, add a component association for
3607 -- the parent field. If the type of the ancestor part is not the direct
3608 -- parent of the expected type, build recursively the needed ancestors.
3609 -- If the ancestor part is a subtype_mark, replace aggregate with a decla-
3610 -- ration for a temporary of the expected type, followed by individual
3611 -- assignments to the given components.
3613 procedure Expand_N_Extension_Aggregate
(N
: Node_Id
) is
3614 Loc
: constant Source_Ptr
:= Sloc
(N
);
3615 A
: constant Node_Id
:= Ancestor_Part
(N
);
3616 Typ
: constant Entity_Id
:= Etype
(N
);
3619 -- If the ancestor is a subtype mark, an init_proc must be called
3620 -- on the resulting object which thus has to be materialized in
3623 if Is_Entity_Name
(A
) and then Is_Type
(Entity
(A
)) then
3624 Convert_To_Assignments
(N
, Typ
);
3626 -- The extension aggregate is transformed into a record aggregate
3627 -- of the following form (c1 and c2 are inherited components)
3629 -- (Exp with c3 => a, c4 => b)
3630 -- ==> (c1 => Exp.c1, c2 => Exp.c2, c1 => a, c2 => b)
3635 -- No tag is needed in the case of Java_VM
3638 Expand_Record_Aggregate
(N
,
3641 Expand_Record_Aggregate
(N
,
3642 Orig_Tag
=> New_Occurrence_Of
(Access_Disp_Table
(Typ
), Loc
),
3646 end Expand_N_Extension_Aggregate
;
3648 -----------------------------
3649 -- Expand_Record_Aggregate --
3650 -----------------------------
3652 procedure Expand_Record_Aggregate
3654 Orig_Tag
: Node_Id
:= Empty
;
3655 Parent_Expr
: Node_Id
:= Empty
)
3657 Loc
: constant Source_Ptr
:= Sloc
(N
);
3658 Comps
: constant List_Id
:= Component_Associations
(N
);
3659 Typ
: constant Entity_Id
:= Etype
(N
);
3660 Base_Typ
: constant Entity_Id
:= Base_Type
(Typ
);
3662 function Has_Delayed_Nested_Aggregate_Or_Tagged_Comps
return Boolean;
3663 -- Checks the presence of a nested aggregate which needs Late_Expansion
3664 -- or the presence of tagged components which may need tag adjustment.
3666 --------------------------------------------------
3667 -- Has_Delayed_Nested_Aggregate_Or_Tagged_Comps --
3668 --------------------------------------------------
3670 function Has_Delayed_Nested_Aggregate_Or_Tagged_Comps
return Boolean is
3680 while Present
(C
) loop
3682 if Nkind
(Expression
(C
)) = N_Qualified_Expression
then
3683 Expr_Q
:= Expression
(Expression
(C
));
3685 Expr_Q
:= Expression
(C
);
3688 -- Return true if the aggregate has any associations for
3689 -- tagged components that may require tag adjustment.
3690 -- These are cases where the source expression may have
3691 -- a tag that could differ from the component tag (e.g.,
3692 -- can occur for type conversions and formal parameters).
3693 -- (Tag adjustment is not needed if Java_VM because object
3694 -- tags are implicit in the JVM.)
3696 if Is_Tagged_Type
(Etype
(Expr_Q
))
3697 and then (Nkind
(Expr_Q
) = N_Type_Conversion
3698 or else (Is_Entity_Name
(Expr_Q
)
3699 and then Ekind
(Entity
(Expr_Q
)) in Formal_Kind
))
3700 and then not Java_VM
3705 if Is_Delayed_Aggregate
(Expr_Q
) then
3713 end Has_Delayed_Nested_Aggregate_Or_Tagged_Comps
;
3715 -- Remaining Expand_Record_Aggregate variables
3717 Tag_Value
: Node_Id
;
3721 -- Start of processing for Expand_Record_Aggregate
3724 -- Gigi doesn't handle properly temporaries of variable size
3725 -- so we generate it in the front-end
3727 if not Size_Known_At_Compile_Time
(Typ
) then
3728 Convert_To_Assignments
(N
, Typ
);
3730 -- Temporaries for controlled aggregates need to be attached to a
3731 -- final chain in order to be properly finalized, so it has to
3732 -- be created in the front-end
3734 elsif Is_Controlled
(Typ
)
3735 or else Has_Controlled_Component
(Base_Type
(Typ
))
3737 Convert_To_Assignments
(N
, Typ
);
3739 elsif Has_Delayed_Nested_Aggregate_Or_Tagged_Comps
then
3740 Convert_To_Assignments
(N
, Typ
);
3742 -- If an ancestor is private, some components are not inherited and
3743 -- we cannot expand into a record aggregate
3745 elsif Has_Private_Ancestor
(Typ
) then
3746 Convert_To_Assignments
(N
, Typ
);
3748 -- ??? The following was done to compile fxacc00.ads in the ACVCs. Gigi
3749 -- is not able to handle the aggregate for Late_Request.
3751 elsif Is_Tagged_Type
(Typ
) and then Has_Discriminants
(Typ
) then
3752 Convert_To_Assignments
(N
, Typ
);
3754 -- In all other cases we generate a proper aggregate that
3755 -- can be handled by gigi.
3758 -- If no discriminants, nothing special to do
3760 if not Has_Discriminants
(Typ
) then
3763 -- Case of discriminants present
3765 elsif Is_Derived_Type
(Typ
) then
3767 -- For untagged types, non-girder discriminants are replaced
3768 -- with girder discriminants, which are the ones that gigi uses
3769 -- to describe the type and its components.
3771 Generate_Aggregate_For_Derived_Type
: declare
3772 First_Comp
: Node_Id
;
3773 Discriminant
: Entity_Id
;
3774 Constraints
: List_Id
:= New_List
;
3776 Num_Disc
: Int
:= 0;
3777 Num_Gird
: Int
:= 0;
3779 procedure Prepend_Girder_Values
(T
: Entity_Id
);
3780 -- Scan the list of girder discriminants of the type, and
3781 -- add their values to the aggregate being built.
3783 ---------------------------
3784 -- Prepend_Girder_Values --
3785 ---------------------------
3787 procedure Prepend_Girder_Values
(T
: Entity_Id
) is
3789 Discriminant
:= First_Girder_Discriminant
(T
);
3791 while Present
(Discriminant
) loop
3793 Make_Component_Association
(Loc
,
3795 New_List
(New_Occurrence_Of
(Discriminant
, Loc
)),
3799 Get_Discriminant_Value
(
3802 Discriminant_Constraint
(Typ
))));
3804 if No
(First_Comp
) then
3805 Prepend_To
(Component_Associations
(N
), New_Comp
);
3807 Insert_After
(First_Comp
, New_Comp
);
3810 First_Comp
:= New_Comp
;
3811 Next_Girder_Discriminant
(Discriminant
);
3813 end Prepend_Girder_Values
;
3815 -- Start of processing for Generate_Aggregate_For_Derived_Type
3818 -- Remove the associations for the discriminant of
3819 -- the derived type.
3821 First_Comp
:= First
(Component_Associations
(N
));
3823 while Present
(First_Comp
) loop
3827 if Ekind
(Entity
(First
(Choices
(Comp
)))) =
3831 Num_Disc
:= Num_Disc
+ 1;
3835 -- Insert girder discriminant associations in the correct
3836 -- order. If there are more girder discriminants than new
3837 -- discriminants, there is at least one new discriminant
3838 -- that constrains more than one of the girders. In this
3839 -- case we need to construct a proper subtype of the parent
3840 -- type, in order to supply values to all the components.
3841 -- Otherwise there is one-one correspondence between the
3842 -- constraints and the girder discriminants.
3844 First_Comp
:= Empty
;
3846 Discriminant
:= First_Girder_Discriminant
(Base_Type
(Typ
));
3848 while Present
(Discriminant
) loop
3849 Num_Gird
:= Num_Gird
+ 1;
3850 Next_Girder_Discriminant
(Discriminant
);
3853 -- Case of more girder discriminants than new discriminants
3855 if Num_Gird
> Num_Disc
then
3857 -- Create a proper subtype of the parent type, which is
3858 -- the proper implementation type for the aggregate, and
3859 -- convert it to the intended target type.
3861 Discriminant
:= First_Girder_Discriminant
(Base_Type
(Typ
));
3863 while Present
(Discriminant
) loop
3866 Get_Discriminant_Value
(
3869 Discriminant_Constraint
(Typ
)));
3870 Append
(New_Comp
, Constraints
);
3871 Next_Girder_Discriminant
(Discriminant
);
3875 Make_Subtype_Declaration
(Loc
,
3876 Defining_Identifier
=>
3877 Make_Defining_Identifier
(Loc
,
3878 New_Internal_Name
('T')),
3879 Subtype_Indication
=>
3880 Make_Subtype_Indication
(Loc
,
3882 New_Occurrence_Of
(Etype
(Base_Type
(Typ
)), Loc
),
3884 Make_Index_Or_Discriminant_Constraint
3885 (Loc
, Constraints
)));
3887 Insert_Action
(N
, Decl
);
3888 Prepend_Girder_Values
(Base_Type
(Typ
));
3890 Set_Etype
(N
, Defining_Identifier
(Decl
));
3893 Rewrite
(N
, Unchecked_Convert_To
(Typ
, N
));
3896 -- Case where we do not have fewer new discriminants than
3897 -- girder discriminants, so in this case we can simply
3898 -- use the girder discriminants of the subtype.
3901 Prepend_Girder_Values
(Typ
);
3903 end Generate_Aggregate_For_Derived_Type
;
3906 if Is_Tagged_Type
(Typ
) then
3908 -- The tagged case, _parent and _tag component must be created.
3910 -- Reset null_present unconditionally. tagged records always have
3911 -- at least one field (the tag or the parent)
3913 Set_Null_Record_Present
(N
, False);
3915 -- When the current aggregate comes from the expansion of an
3916 -- extension aggregate, the parent expr is replaced by an
3917 -- aggregate formed by selected components of this expr
3919 if Present
(Parent_Expr
)
3920 and then Is_Empty_List
(Comps
)
3922 Comp
:= First_Entity
(Typ
);
3923 while Present
(Comp
) loop
3925 -- Skip all entities that aren't discriminants or components
3927 if Ekind
(Comp
) /= E_Discriminant
3928 and then Ekind
(Comp
) /= E_Component
3932 -- Skip all expander-generated components
3935 not Comes_From_Source
(Original_Record_Component
(Comp
))
3941 Make_Selected_Component
(Loc
,
3943 Unchecked_Convert_To
(Typ
,
3944 Duplicate_Subexpr
(Parent_Expr
, True)),
3946 Selector_Name
=> New_Occurrence_Of
(Comp
, Loc
));
3949 Make_Component_Association
(Loc
,
3951 New_List
(New_Occurrence_Of
(Comp
, Loc
)),
3955 Analyze_And_Resolve
(New_Comp
, Etype
(Comp
));
3962 -- Compute the value for the Tag now, if the type is a root it
3963 -- will be included in the aggregate right away, otherwise it will
3964 -- be propagated to the parent aggregate
3966 if Present
(Orig_Tag
) then
3967 Tag_Value
:= Orig_Tag
;
3971 Tag_Value
:= New_Occurrence_Of
(Access_Disp_Table
(Typ
), Loc
);
3974 -- For a derived type, an aggregate for the parent is formed with
3975 -- all the inherited components.
3977 if Is_Derived_Type
(Typ
) then
3980 First_Comp
: Node_Id
;
3981 Parent_Comps
: List_Id
;
3982 Parent_Aggr
: Node_Id
;
3983 Parent_Name
: Node_Id
;
3986 -- Remove the inherited component association from the
3987 -- aggregate and store them in the parent aggregate
3989 First_Comp
:= First
(Component_Associations
(N
));
3990 Parent_Comps
:= New_List
;
3992 while Present
(First_Comp
)
3993 and then Scope
(Original_Record_Component
(
3994 Entity
(First
(Choices
(First_Comp
))))) /= Base_Typ
3999 Append
(Comp
, Parent_Comps
);
4002 Parent_Aggr
:= Make_Aggregate
(Loc
,
4003 Component_Associations
=> Parent_Comps
);
4004 Set_Etype
(Parent_Aggr
, Etype
(Base_Type
(Typ
)));
4006 -- Find the _parent component
4008 Comp
:= First_Component
(Typ
);
4009 while Chars
(Comp
) /= Name_uParent
loop
4010 Comp
:= Next_Component
(Comp
);
4013 Parent_Name
:= New_Occurrence_Of
(Comp
, Loc
);
4015 -- Insert the parent aggregate
4017 Prepend_To
(Component_Associations
(N
),
4018 Make_Component_Association
(Loc
,
4019 Choices
=> New_List
(Parent_Name
),
4020 Expression
=> Parent_Aggr
));
4022 -- Expand recursively the parent propagating the right Tag
4024 Expand_Record_Aggregate
(
4025 Parent_Aggr
, Tag_Value
, Parent_Expr
);
4028 -- For a root type, the tag component is added (unless compiling
4029 -- for the Java VM, where tags are implicit).
4031 elsif not Java_VM
then
4033 Tag_Name
: constant Node_Id
:=
4034 New_Occurrence_Of
(Tag_Component
(Typ
), Loc
);
4035 Typ_Tag
: constant Entity_Id
:= RTE
(RE_Tag
);
4036 Conv_Node
: constant Node_Id
:=
4037 Unchecked_Convert_To
(Typ_Tag
, Tag_Value
);
4040 Set_Etype
(Conv_Node
, Typ_Tag
);
4041 Prepend_To
(Component_Associations
(N
),
4042 Make_Component_Association
(Loc
,
4043 Choices
=> New_List
(Tag_Name
),
4044 Expression
=> Conv_Node
));
4049 end Expand_Record_Aggregate
;
4051 --------------------------
4052 -- Is_Delayed_Aggregate --
4053 --------------------------
4055 function Is_Delayed_Aggregate
(N
: Node_Id
) return Boolean is
4056 Node
: Node_Id
:= N
;
4057 Kind
: Node_Kind
:= Nkind
(Node
);
4059 if Kind
= N_Qualified_Expression
then
4060 Node
:= Expression
(Node
);
4061 Kind
:= Nkind
(Node
);
4064 if Kind
/= N_Aggregate
and then Kind
/= N_Extension_Aggregate
then
4067 return Expansion_Delayed
(Node
);
4069 end Is_Delayed_Aggregate
;
4071 --------------------
4072 -- Late_Expansion --
4073 --------------------
4075 function Late_Expansion
4079 Flist
: Node_Id
:= Empty
;
4080 Obj
: Entity_Id
:= Empty
)
4085 if Is_Record_Type
(Etype
(N
)) then
4086 return Build_Record_Aggr_Code
(N
, Typ
, Target
, Flist
, Obj
);
4089 Build_Array_Aggr_Code
4093 Is_Scalar_Type
(Component_Type
(Typ
)),
4099 ----------------------------------
4100 -- Make_OK_Assignment_Statement --
4101 ----------------------------------
4103 function Make_OK_Assignment_Statement
4106 Expression
: Node_Id
)
4110 Set_Assignment_OK
(Name
);
4111 return Make_Assignment_Statement
(Sloc
, Name
, Expression
);
4112 end Make_OK_Assignment_Statement
;
4114 -----------------------
4115 -- Number_Of_Choices --
4116 -----------------------
4118 function Number_Of_Choices
(N
: Node_Id
) return Nat
is
4122 Nb_Choices
: Nat
:= 0;
4125 if Present
(Expressions
(N
)) then
4129 Assoc
:= First
(Component_Associations
(N
));
4130 while Present
(Assoc
) loop
4132 Choice
:= First
(Choices
(Assoc
));
4133 while Present
(Choice
) loop
4135 if Nkind
(Choice
) /= N_Others_Choice
then
4136 Nb_Choices
:= Nb_Choices
+ 1;
4146 end Number_Of_Choices
;
4148 ------------------------------------
4149 -- Packed_Array_Aggregate_Handled --
4150 ------------------------------------
4152 -- The current version of this procedure will handle at compile time
4153 -- any array aggregate that meets these conditions:
4155 -- One dimensional, bit packed
4156 -- Underlying packed type is modular type
4157 -- Bounds are within 32-bit Int range
4158 -- All bounds and values are static
4160 function Packed_Array_Aggregate_Handled
(N
: Node_Id
) return Boolean is
4161 Loc
: constant Source_Ptr
:= Sloc
(N
);
4162 Typ
: constant Entity_Id
:= Etype
(N
);
4163 Ctyp
: constant Entity_Id
:= Component_Type
(Typ
);
4165 Not_Handled
: exception;
4166 -- Exception raised if this aggregate cannot be handled
4169 -- For now, handle only one dimensional bit packed arrays
4171 if not Is_Bit_Packed_Array
(Typ
)
4172 or else Number_Dimensions
(Typ
) > 1
4173 or else not Is_Modular_Integer_Type
(Packed_Array_Type
(Typ
))
4179 Csiz
: constant Nat
:= UI_To_Int
(Component_Size
(Typ
));
4183 -- Bounds of index type
4187 -- Values of bounds if compile time known
4189 function Get_Component_Val
(N
: Node_Id
) return Uint
;
4190 -- Given a expression value N of the component type Ctyp, returns
4191 -- A value of Csiz (component size) bits representing this value.
4192 -- If the value is non-static or any other reason exists why the
4193 -- value cannot be returned, then Not_Handled is raised.
4195 -----------------------
4196 -- Get_Component_Val --
4197 -----------------------
4199 function Get_Component_Val
(N
: Node_Id
) return Uint
is
4203 -- We have to analyze the expression here before doing any further
4204 -- processing here. The analysis of such expressions is deferred
4205 -- till expansion to prevent some problems of premature analysis.
4207 Analyze_And_Resolve
(N
, Ctyp
);
4209 -- Must have a compile time value
4211 if not Compile_Time_Known_Value
(N
) then
4215 Val
:= Expr_Rep_Value
(N
);
4217 -- Adjust for bias, and strip proper number of bits
4219 if Has_Biased_Representation
(Ctyp
) then
4220 Val
:= Val
- Expr_Value
(Type_Low_Bound
(Ctyp
));
4223 return Val
mod Uint_2
** Csiz
;
4224 end Get_Component_Val
;
4226 -- Here we know we have a one dimensional bit packed array
4229 Get_Index_Bounds
(First_Index
(Typ
), Lo
, Hi
);
4231 -- Cannot do anything if bounds are dynamic
4233 if not Compile_Time_Known_Value
(Lo
)
4235 not Compile_Time_Known_Value
(Hi
)
4240 -- Or are silly out of range of int bounds
4242 Lob
:= Expr_Value
(Lo
);
4243 Hib
:= Expr_Value
(Hi
);
4245 if not UI_Is_In_Int_Range
(Lob
)
4247 not UI_Is_In_Int_Range
(Hib
)
4252 -- At this stage we have a suitable aggregate for handling
4253 -- at compile time (the only remaining checks, are that the
4254 -- values of expressions in the aggregate are compile time
4255 -- known (check performed by Get_Component_Val), and that
4256 -- any subtypes or ranges are statically known.
4258 -- If the aggregate is not fully positional at this stage,
4259 -- then convert it to positional form. Either this will fail,
4260 -- in which case we can do nothing, or it will succeed, in
4261 -- which case we have succeeded in handling the aggregate,
4262 -- or it will stay an aggregate, in which case we have failed
4263 -- to handle this case.
4265 if Present
(Component_Associations
(N
)) then
4266 Convert_To_Positional
4267 (N
, Max_Others_Replicate
=> 64, Handle_Bit_Packed
=> True);
4268 return Nkind
(N
) /= N_Aggregate
;
4271 -- Otherwise we are all positional, so convert to proper value
4274 Lov
: constant Nat
:= UI_To_Int
(Lob
);
4275 Hiv
: constant Nat
:= UI_To_Int
(Hib
);
4277 Len
: constant Nat
:= Int
'Max (0, Hiv
- Lov
+ 1);
4278 -- The length of the array (number of elements)
4280 Aggregate_Val
: Uint
;
4281 -- Value of aggregate. The value is set in the low order
4282 -- bits of this value. For the little-endian case, the
4283 -- values are stored from low-order to high-order and
4284 -- for the big-endian case the values are stored from
4285 -- high-order to low-order. Note that gigi will take care
4286 -- of the conversions to left justify the value in the big
4287 -- endian case (because of left justified modular type
4288 -- processing), so we do not have to worry about that here.
4291 -- Integer literal for resulting constructed value
4294 -- Shift count from low order for next value
4297 -- Shift increment for loop
4300 -- Next expression from positional parameters of aggregate
4303 -- For little endian, we fill up the low order bits of the
4304 -- target value. For big endian we fill up the high order
4305 -- bits of the target value (which is a left justified
4308 if Bytes_Big_Endian
xor Debug_Flag_8
then
4309 Shift
:= Csiz
* (Len
- 1);
4316 -- Loop to set the values
4318 Aggregate_Val
:= Uint_0
;
4319 Expr
:= First
(Expressions
(N
));
4320 for J
in 1 .. Len
loop
4322 Aggregate_Val
+ Get_Component_Val
(Expr
) * Uint_2
** Shift
;
4323 Shift
:= Shift
+ Incr
;
4327 -- Now we can rewrite with the proper value
4330 Make_Integer_Literal
(Loc
,
4331 Intval
=> Aggregate_Val
);
4332 Set_Print_In_Hex
(Lit
);
4334 -- Construct the expression using this literal. Note that it is
4335 -- important to qualify the literal with its proper modular type
4336 -- since universal integer does not have the required range and
4337 -- also this is a left justified modular type, which is important
4338 -- in the big-endian case.
4341 Unchecked_Convert_To
(Typ
,
4342 Make_Qualified_Expression
(Loc
,
4344 New_Occurrence_Of
(Packed_Array_Type
(Typ
), Loc
),
4345 Expression
=> Lit
)));
4347 Analyze_And_Resolve
(N
, Typ
);
4355 end Packed_Array_Aggregate_Handled
;
4357 ------------------------------
4358 -- Initialize_Discriminants --
4359 ------------------------------
4361 procedure Initialize_Discriminants
(N
: Node_Id
; Typ
: Entity_Id
) is
4362 Loc
: constant Source_Ptr
:= Sloc
(N
);
4363 Bas
: constant Entity_Id
:= Base_Type
(Typ
);
4364 Par
: constant Entity_Id
:= Etype
(Bas
);
4365 Decl
: constant Node_Id
:= Parent
(Par
);
4369 if Is_Tagged_Type
(Bas
)
4370 and then Is_Derived_Type
(Bas
)
4371 and then Has_Discriminants
(Par
)
4372 and then Has_Discriminants
(Bas
)
4373 and then Number_Discriminants
(Bas
) /= Number_Discriminants
(Par
)
4374 and then Nkind
(Decl
) = N_Full_Type_Declaration
4375 and then Nkind
(Type_Definition
(Decl
)) = N_Record_Definition
4377 (Variant_Part
(Component_List
(Type_Definition
(Decl
))))
4378 and then Nkind
(N
) /= N_Extension_Aggregate
4381 -- Call init_proc to set discriminants.
4382 -- There should eventually be a special procedure for this ???
4384 Ref
:= New_Reference_To
(Defining_Identifier
(N
), Loc
);
4385 Insert_Actions_After
(N
,
4386 Build_Initialization_Call
(Sloc
(N
), Ref
, Typ
));
4388 end Initialize_Discriminants
;
4390 ---------------------------
4391 -- Safe_Slice_Assignment --
4392 ---------------------------
4394 function Safe_Slice_Assignment
(N
: Node_Id
) return Boolean is
4395 Loc
: constant Source_Ptr
:= Sloc
(Parent
(N
));
4396 Pref
: constant Node_Id
:= Prefix
(Name
(Parent
(N
)));
4397 Range_Node
: constant Node_Id
:= Discrete_Range
(Name
(Parent
(N
)));
4405 -- Generate: for J in Range loop Pref (J) := Expr; end loop;
4407 if Comes_From_Source
(N
)
4408 and then No
(Expressions
(N
))
4409 and then Nkind
(First
(Choices
(First
(Component_Associations
(N
)))))
4413 Expression
(First
(Component_Associations
(N
)));
4414 L_J
:= Make_Defining_Identifier
(Loc
, New_Internal_Name
('J'));
4417 Make_Iteration_Scheme
(Loc
,
4418 Loop_Parameter_Specification
=>
4419 Make_Loop_Parameter_Specification
4421 Defining_Identifier
=> L_J
,
4422 Discrete_Subtype_Definition
=> Relocate_Node
(Range_Node
)));
4425 Make_Assignment_Statement
(Loc
,
4427 Make_Indexed_Component
(Loc
,
4428 Prefix
=> Relocate_Node
(Pref
),
4429 Expressions
=> New_List
(New_Occurrence_Of
(L_J
, Loc
))),
4430 Expression
=> Relocate_Node
(Expr
));
4432 -- Construct the final loop
4435 Make_Implicit_Loop_Statement
4436 (Node
=> Parent
(N
),
4437 Identifier
=> Empty
,
4438 Iteration_Scheme
=> L_Iter
,
4439 Statements
=> New_List
(L_Body
));
4441 Rewrite
(Parent
(N
), Stat
);
4442 Analyze
(Parent
(N
));
4448 end Safe_Slice_Assignment
;
4450 ---------------------
4451 -- Sort_Case_Table --
4452 ---------------------
4454 procedure Sort_Case_Table
(Case_Table
: in out Case_Table_Type
) is
4455 L
: Int
:= Case_Table
'First;
4456 U
: Int
:= Case_Table
'Last;
4465 T
:= Case_Table
(K
+ 1);
4469 and then Expr_Value
(Case_Table
(J
- 1).Choice_Lo
) >
4470 Expr_Value
(T
.Choice_Lo
)
4472 Case_Table
(J
) := Case_Table
(J
- 1);
4476 Case_Table
(J
) := T
;
4479 end Sort_Case_Table
;