PR testsuite/39776
[official-gcc.git] / gcc / ada / exp_aggr.adb
blob516905f88732298ce52945b946493da9791e48be
1 ------------------------------------------------------------------------------
2 -- --
3 -- GNAT COMPILER COMPONENTS --
4 -- --
5 -- E X P _ A G G R --
6 -- --
7 -- B o d y --
8 -- --
9 -- Copyright (C) 1992-2009, Free Software Foundation, Inc. --
10 -- --
11 -- GNAT is free software; you can redistribute it and/or modify it under --
12 -- terms of the GNU General Public License as published by the Free Soft- --
13 -- ware Foundation; either version 3, or (at your option) any later ver- --
14 -- sion. GNAT is distributed in the hope that it will be useful, but WITH- --
15 -- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY --
16 -- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License --
17 -- for more details. You should have received a copy of the GNU General --
18 -- Public License distributed with GNAT; see file COPYING3. If not, go to --
19 -- http://www.gnu.org/licenses for a complete copy of the license. --
20 -- --
21 -- GNAT was originally developed by the GNAT team at New York University. --
22 -- Extensive contributions were provided by Ada Core Technologies Inc. --
23 -- --
24 ------------------------------------------------------------------------------
26 with Atree; use Atree;
27 with Checks; use Checks;
28 with Debug; use Debug;
29 with Einfo; use Einfo;
30 with Elists; use Elists;
31 with Errout; use Errout;
32 with Expander; use Expander;
33 with Exp_Util; use Exp_Util;
34 with Exp_Ch3; use Exp_Ch3;
35 with Exp_Ch7; use Exp_Ch7;
36 with Exp_Ch9; use Exp_Ch9;
37 with Exp_Tss; use Exp_Tss;
38 with Fname; use Fname;
39 with Freeze; use Freeze;
40 with Itypes; use Itypes;
41 with Lib; use Lib;
42 with Namet; use Namet;
43 with Nmake; use Nmake;
44 with Nlists; use Nlists;
45 with Opt; use Opt;
46 with Restrict; use Restrict;
47 with Rident; use Rident;
48 with Rtsfind; use Rtsfind;
49 with Ttypes; use Ttypes;
50 with Sem; use Sem;
51 with Sem_Aux; use Sem_Aux;
52 with Sem_Ch3; use Sem_Ch3;
53 with Sem_Eval; use Sem_Eval;
54 with Sem_Res; use Sem_Res;
55 with Sem_Util; use Sem_Util;
56 with Sinfo; use Sinfo;
57 with Snames; use Snames;
58 with Stand; use Stand;
59 with Targparm; use Targparm;
60 with Tbuild; use Tbuild;
61 with Uintp; use Uintp;
63 package body Exp_Aggr is
65 type Case_Bounds is record
66 Choice_Lo : Node_Id;
67 Choice_Hi : Node_Id;
68 Choice_Node : Node_Id;
69 end record;
71 type Case_Table_Type is array (Nat range <>) of Case_Bounds;
72 -- Table type used by Check_Case_Choices procedure
74 function Must_Slide
75 (Obj_Type : Entity_Id;
76 Typ : Entity_Id) return Boolean;
77 -- A static array aggregate in an object declaration can in most cases be
78 -- expanded in place. The one exception is when the aggregate is given
79 -- with component associations that specify different bounds from those of
80 -- the type definition in the object declaration. In this pathological
81 -- case the aggregate must slide, and we must introduce an intermediate
82 -- temporary to hold it.
84 -- The same holds in an assignment to one-dimensional array of arrays,
85 -- when a component may be given with bounds that differ from those of the
86 -- component type.
88 procedure Sort_Case_Table (Case_Table : in out Case_Table_Type);
89 -- Sort the Case Table using the Lower Bound of each Choice as the key.
90 -- A simple insertion sort is used since the number of choices in a case
91 -- statement of variant part will usually be small and probably in near
92 -- sorted order.
94 function Has_Default_Init_Comps (N : Node_Id) return Boolean;
95 -- N is an aggregate (record or array). Checks the presence of default
96 -- initialization (<>) in any component (Ada 2005: AI-287)
98 function Is_Static_Dispatch_Table_Aggregate (N : Node_Id) return Boolean;
99 -- Returns true if N is an aggregate used to initialize the components
100 -- of an statically allocated dispatch table.
102 ------------------------------------------------------
103 -- Local subprograms for Record Aggregate Expansion --
104 ------------------------------------------------------
106 procedure Expand_Record_Aggregate
107 (N : Node_Id;
108 Orig_Tag : Node_Id := Empty;
109 Parent_Expr : Node_Id := Empty);
110 -- This is the top level procedure for record aggregate expansion.
111 -- Expansion for record aggregates needs expand aggregates for tagged
112 -- record types. Specifically Expand_Record_Aggregate adds the Tag
113 -- field in front of the Component_Association list that was created
114 -- during resolution by Resolve_Record_Aggregate.
116 -- N is the record aggregate node.
117 -- Orig_Tag is the value of the Tag that has to be provided for this
118 -- specific aggregate. It carries the tag corresponding to the type
119 -- of the outermost aggregate during the recursive expansion
120 -- Parent_Expr is the ancestor part of the original extension
121 -- aggregate
123 procedure Convert_To_Assignments (N : Node_Id; Typ : Entity_Id);
124 -- N is an N_Aggregate or an N_Extension_Aggregate. Typ is the type of the
125 -- aggregate (which can only be a record type, this procedure is only used
126 -- for record types). Transform the given aggregate into a sequence of
127 -- assignments performed component by component.
129 function Build_Record_Aggr_Code
130 (N : Node_Id;
131 Typ : Entity_Id;
132 Lhs : Node_Id;
133 Flist : Node_Id := Empty;
134 Obj : Entity_Id := Empty;
135 Is_Limited_Ancestor_Expansion : Boolean := False) return List_Id;
136 -- N is an N_Aggregate or an N_Extension_Aggregate. Typ is the type of the
137 -- aggregate. Target is an expression containing the location on which the
138 -- component by component assignments will take place. Returns the list of
139 -- assignments plus all other adjustments needed for tagged and controlled
140 -- types. Flist is an expression representing the finalization list on
141 -- which to attach the controlled components if any. Obj is present in the
142 -- object declaration and dynamic allocation cases, it contains an entity
143 -- that allows to know if the value being created needs to be attached to
144 -- the final list in case of pragma Finalize_Storage_Only.
146 -- ???
147 -- The meaning of the Obj formal is extremely unclear. *What* entity
148 -- should be passed? For the object declaration case we may guess that
149 -- this is the object being declared, but what about the allocator case?
151 -- Is_Limited_Ancestor_Expansion indicates that the function has been
152 -- called recursively to expand the limited ancestor to avoid copying it.
154 function Has_Mutable_Components (Typ : Entity_Id) return Boolean;
155 -- Return true if one of the component is of a discriminated type with
156 -- defaults. An aggregate for a type with mutable components must be
157 -- expanded into individual assignments.
159 procedure Initialize_Discriminants (N : Node_Id; Typ : Entity_Id);
160 -- If the type of the aggregate is a type extension with renamed discrimi-
161 -- nants, we must initialize the hidden discriminants of the parent.
162 -- Otherwise, the target object must not be initialized. The discriminants
163 -- are initialized by calling the initialization procedure for the type.
164 -- This is incorrect if the initialization of other components has any
165 -- side effects. We restrict this call to the case where the parent type
166 -- has a variant part, because this is the only case where the hidden
167 -- discriminants are accessed, namely when calling discriminant checking
168 -- functions of the parent type, and when applying a stream attribute to
169 -- an object of the derived type.
171 -----------------------------------------------------
172 -- Local Subprograms for Array Aggregate Expansion --
173 -----------------------------------------------------
175 function Aggr_Size_OK (N : Node_Id; Typ : Entity_Id) return Boolean;
176 -- Very large static aggregates present problems to the back-end, and
177 -- are transformed into assignments and loops. This function verifies
178 -- that the total number of components of an aggregate is acceptable
179 -- for transformation into a purely positional static form. It is called
180 -- prior to calling Flatten.
181 -- This function also detects and warns about one-component aggregates
182 -- that appear in a non-static context. Even if the component value is
183 -- static, such an aggregate must be expanded into an assignment.
185 procedure Convert_Array_Aggr_In_Allocator
186 (Decl : Node_Id;
187 Aggr : Node_Id;
188 Target : Node_Id);
189 -- If the aggregate appears within an allocator and can be expanded in
190 -- place, this routine generates the individual assignments to components
191 -- of the designated object. This is an optimization over the general
192 -- case, where a temporary is first created on the stack and then used to
193 -- construct the allocated object on the heap.
195 procedure Convert_To_Positional
196 (N : Node_Id;
197 Max_Others_Replicate : Nat := 5;
198 Handle_Bit_Packed : Boolean := False);
199 -- If possible, convert named notation to positional notation. This
200 -- conversion is possible only in some static cases. If the conversion is
201 -- possible, then N is rewritten with the analyzed converted aggregate.
202 -- The parameter Max_Others_Replicate controls the maximum number of
203 -- values corresponding to an others choice that will be converted to
204 -- positional notation (the default of 5 is the normal limit, and reflects
205 -- the fact that normally the loop is better than a lot of separate
206 -- assignments). Note that this limit gets overridden in any case if
207 -- either of the restrictions No_Elaboration_Code or No_Implicit_Loops is
208 -- set. The parameter Handle_Bit_Packed is usually set False (since we do
209 -- not expect the back end to handle bit packed arrays, so the normal case
210 -- of conversion is pointless), but in the special case of a call from
211 -- Packed_Array_Aggregate_Handled, we set this parameter to True, since
212 -- these are cases we handle in there.
214 procedure Expand_Array_Aggregate (N : Node_Id);
215 -- This is the top-level routine to perform array aggregate expansion.
216 -- N is the N_Aggregate node to be expanded.
218 function Backend_Processing_Possible (N : Node_Id) return Boolean;
219 -- This function checks if array aggregate N can be processed directly
220 -- by Gigi. If this is the case True is returned.
222 function Build_Array_Aggr_Code
223 (N : Node_Id;
224 Ctype : Entity_Id;
225 Index : Node_Id;
226 Into : Node_Id;
227 Scalar_Comp : Boolean;
228 Indices : List_Id := No_List;
229 Flist : Node_Id := Empty) return List_Id;
230 -- This recursive routine returns a list of statements containing the
231 -- loops and assignments that are needed for the expansion of the array
232 -- aggregate N.
234 -- N is the (sub-)aggregate node to be expanded into code. This node
235 -- has been fully analyzed, and its Etype is properly set.
237 -- Index is the index node corresponding to the array sub-aggregate N.
239 -- Into is the target expression into which we are copying the aggregate.
240 -- Note that this node may not have been analyzed yet, and so the Etype
241 -- field may not be set.
243 -- Scalar_Comp is True if the component type of the aggregate is scalar.
245 -- Indices is the current list of expressions used to index the
246 -- object we are writing into.
248 -- Flist is an expression representing the finalization list on which
249 -- to attach the controlled components if any.
251 function Number_Of_Choices (N : Node_Id) return Nat;
252 -- Returns the number of discrete choices (not including the others choice
253 -- if present) contained in (sub-)aggregate N.
255 function Late_Expansion
256 (N : Node_Id;
257 Typ : Entity_Id;
258 Target : Node_Id;
259 Flist : Node_Id := Empty;
260 Obj : Entity_Id := Empty) return List_Id;
261 -- N is a nested (record or array) aggregate that has been marked with
262 -- 'Delay_Expansion'. Typ is the expected type of the aggregate and Target
263 -- is a (duplicable) expression that will hold the result of the aggregate
264 -- expansion. Flist is the finalization list to be used to attach
265 -- controlled components. 'Obj' when non empty, carries the original
266 -- object being initialized in order to know if it needs to be attached to
267 -- the previous parameter which may not be the case in the case where
268 -- Finalize_Storage_Only is set. Basically this procedure is used to
269 -- implement top-down expansions of nested aggregates. This is necessary
270 -- for avoiding temporaries at each level as well as for propagating the
271 -- right internal finalization list.
273 function Make_OK_Assignment_Statement
274 (Sloc : Source_Ptr;
275 Name : Node_Id;
276 Expression : Node_Id) return Node_Id;
277 -- This is like Make_Assignment_Statement, except that Assignment_OK
278 -- is set in the left operand. All assignments built by this unit
279 -- use this routine. This is needed to deal with assignments to
280 -- initialized constants that are done in place.
282 function Packed_Array_Aggregate_Handled (N : Node_Id) return Boolean;
283 -- Given an array aggregate, this function handles the case of a packed
284 -- array aggregate with all constant values, where the aggregate can be
285 -- evaluated at compile time. If this is possible, then N is rewritten
286 -- to be its proper compile time value with all the components properly
287 -- assembled. The expression is analyzed and resolved and True is
288 -- returned. If this transformation is not possible, N is unchanged
289 -- and False is returned
291 function Safe_Slice_Assignment (N : Node_Id) return Boolean;
292 -- If a slice assignment has an aggregate with a single others_choice,
293 -- the assignment can be done in place even if bounds are not static,
294 -- by converting it into a loop over the discrete range of the slice.
296 ------------------
297 -- Aggr_Size_OK --
298 ------------------
300 function Aggr_Size_OK (N : Node_Id; Typ : Entity_Id) return Boolean is
301 Lo : Node_Id;
302 Hi : Node_Id;
303 Indx : Node_Id;
304 Siz : Int;
305 Lov : Uint;
306 Hiv : Uint;
308 -- The following constant determines the maximum size of an
309 -- array aggregate produced by converting named to positional
310 -- notation (e.g. from others clauses). This avoids running
311 -- away with attempts to convert huge aggregates, which hit
312 -- memory limits in the backend.
314 -- The normal limit is 5000, but we increase this limit to
315 -- 2**24 (about 16 million) if Restrictions (No_Elaboration_Code)
316 -- or Restrictions (No_Implicit_Loops) is specified, since in
317 -- either case, we are at risk of declaring the program illegal
318 -- because of this limit.
320 Max_Aggr_Size : constant Nat :=
321 5000 + (2 ** 24 - 5000) *
322 Boolean'Pos
323 (Restriction_Active (No_Elaboration_Code)
324 or else
325 Restriction_Active (No_Implicit_Loops));
327 function Component_Count (T : Entity_Id) return Int;
328 -- The limit is applied to the total number of components that the
329 -- aggregate will have, which is the number of static expressions
330 -- that will appear in the flattened array. This requires a recursive
331 -- computation of the number of scalar components of the structure.
333 ---------------------
334 -- Component_Count --
335 ---------------------
337 function Component_Count (T : Entity_Id) return Int is
338 Res : Int := 0;
339 Comp : Entity_Id;
341 begin
342 if Is_Scalar_Type (T) then
343 return 1;
345 elsif Is_Record_Type (T) then
346 Comp := First_Component (T);
347 while Present (Comp) loop
348 Res := Res + Component_Count (Etype (Comp));
349 Next_Component (Comp);
350 end loop;
352 return Res;
354 elsif Is_Array_Type (T) then
355 declare
356 Lo : constant Node_Id :=
357 Type_Low_Bound (Etype (First_Index (T)));
358 Hi : constant Node_Id :=
359 Type_High_Bound (Etype (First_Index (T)));
361 Siz : constant Int := Component_Count (Component_Type (T));
363 begin
364 if not Compile_Time_Known_Value (Lo)
365 or else not Compile_Time_Known_Value (Hi)
366 then
367 return 0;
368 else
369 return
370 Siz * UI_To_Int (Expr_Value (Hi) - Expr_Value (Lo) + 1);
371 end if;
372 end;
374 else
375 -- Can only be a null for an access type
377 return 1;
378 end if;
379 end Component_Count;
381 -- Start of processing for Aggr_Size_OK
383 begin
384 Siz := Component_Count (Component_Type (Typ));
386 Indx := First_Index (Typ);
387 while Present (Indx) loop
388 Lo := Type_Low_Bound (Etype (Indx));
389 Hi := Type_High_Bound (Etype (Indx));
391 -- Bounds need to be known at compile time
393 if not Compile_Time_Known_Value (Lo)
394 or else not Compile_Time_Known_Value (Hi)
395 then
396 return False;
397 end if;
399 Lov := Expr_Value (Lo);
400 Hiv := Expr_Value (Hi);
402 -- A flat array is always safe
404 if Hiv < Lov then
405 return True;
406 end if;
408 -- One-component aggregates are suspicious, and if the context type
409 -- is an object declaration with non-static bounds it will trip gcc;
410 -- such an aggregate must be expanded into a single assignment.
412 if Hiv = Lov
413 and then Nkind (Parent (N)) = N_Object_Declaration
414 then
415 declare
416 Index_Type : constant Entity_Id :=
417 Etype
418 (First_Index
419 (Etype (Defining_Identifier (Parent (N)))));
420 Indx : Node_Id;
422 begin
423 if not Compile_Time_Known_Value (Type_Low_Bound (Index_Type))
424 or else not Compile_Time_Known_Value
425 (Type_High_Bound (Index_Type))
426 then
427 if Present (Component_Associations (N)) then
428 Indx :=
429 First (Choices (First (Component_Associations (N))));
430 if Is_Entity_Name (Indx)
431 and then not Is_Type (Entity (Indx))
432 then
433 Error_Msg_N
434 ("single component aggregate in non-static context?",
435 Indx);
436 Error_Msg_N ("\maybe subtype name was meant?", Indx);
437 end if;
438 end if;
440 return False;
441 end if;
442 end;
443 end if;
445 declare
446 Rng : constant Uint := Hiv - Lov + 1;
448 begin
449 -- Check if size is too large
451 if not UI_Is_In_Int_Range (Rng) then
452 return False;
453 end if;
455 Siz := Siz * UI_To_Int (Rng);
456 end;
458 if Siz <= 0
459 or else Siz > Max_Aggr_Size
460 then
461 return False;
462 end if;
464 -- Bounds must be in integer range, for later array construction
466 if not UI_Is_In_Int_Range (Lov)
467 or else
468 not UI_Is_In_Int_Range (Hiv)
469 then
470 return False;
471 end if;
473 Next_Index (Indx);
474 end loop;
476 return True;
477 end Aggr_Size_OK;
479 ---------------------------------
480 -- Backend_Processing_Possible --
481 ---------------------------------
483 -- Backend processing by Gigi/gcc is possible only if all the following
484 -- conditions are met:
486 -- 1. N is fully positional
488 -- 2. N is not a bit-packed array aggregate;
490 -- 3. The size of N's array type must be known at compile time. Note
491 -- that this implies that the component size is also known
493 -- 4. The array type of N does not follow the Fortran layout convention
494 -- or if it does it must be 1 dimensional.
496 -- 5. The array component type may not be tagged (which could necessitate
497 -- reassignment of proper tags).
499 -- 6. The array component type must not have unaligned bit components
501 -- 7. None of the components of the aggregate may be bit unaligned
502 -- components.
504 -- 8. There cannot be delayed components, since we do not know enough
505 -- at this stage to know if back end processing is possible.
507 -- 9. There cannot be any discriminated record components, since the
508 -- back end cannot handle this complex case.
510 -- 10. No controlled actions need to be generated for components
512 function Backend_Processing_Possible (N : Node_Id) return Boolean is
513 Typ : constant Entity_Id := Etype (N);
514 -- Typ is the correct constrained array subtype of the aggregate
516 function Component_Check (N : Node_Id; Index : Node_Id) return Boolean;
517 -- This routine checks components of aggregate N, enforcing checks
518 -- 1, 7, 8, and 9. In the multi-dimensional case, these checks are
519 -- performed on subaggregates. The Index value is the current index
520 -- being checked in the multi-dimensional case.
522 ---------------------
523 -- Component_Check --
524 ---------------------
526 function Component_Check (N : Node_Id; Index : Node_Id) return Boolean is
527 Expr : Node_Id;
529 begin
530 -- Checks 1: (no component associations)
532 if Present (Component_Associations (N)) then
533 return False;
534 end if;
536 -- Checks on components
538 -- Recurse to check subaggregates, which may appear in qualified
539 -- expressions. If delayed, the front-end will have to expand.
540 -- If the component is a discriminated record, treat as non-static,
541 -- as the back-end cannot handle this properly.
543 Expr := First (Expressions (N));
544 while Present (Expr) loop
546 -- Checks 8: (no delayed components)
548 if Is_Delayed_Aggregate (Expr) then
549 return False;
550 end if;
552 -- Checks 9: (no discriminated records)
554 if Present (Etype (Expr))
555 and then Is_Record_Type (Etype (Expr))
556 and then Has_Discriminants (Etype (Expr))
557 then
558 return False;
559 end if;
561 -- Checks 7. Component must not be bit aligned component
563 if Possible_Bit_Aligned_Component (Expr) then
564 return False;
565 end if;
567 -- Recursion to following indexes for multiple dimension case
569 if Present (Next_Index (Index))
570 and then not Component_Check (Expr, Next_Index (Index))
571 then
572 return False;
573 end if;
575 -- All checks for that component finished, on to next
577 Next (Expr);
578 end loop;
580 return True;
581 end Component_Check;
583 -- Start of processing for Backend_Processing_Possible
585 begin
586 -- Checks 2 (array not bit packed) and 10 (no controlled actions)
588 if Is_Bit_Packed_Array (Typ) or else Needs_Finalization (Typ) then
589 return False;
590 end if;
592 -- If component is limited, aggregate must be expanded because each
593 -- component assignment must be built in place.
595 if Is_Inherently_Limited_Type (Component_Type (Typ)) then
596 return False;
597 end if;
599 -- Checks 4 (array must not be multi-dimensional Fortran case)
601 if Convention (Typ) = Convention_Fortran
602 and then Number_Dimensions (Typ) > 1
603 then
604 return False;
605 end if;
607 -- Checks 3 (size of array must be known at compile time)
609 if not Size_Known_At_Compile_Time (Typ) then
610 return False;
611 end if;
613 -- Checks on components
615 if not Component_Check (N, First_Index (Typ)) then
616 return False;
617 end if;
619 -- Checks 5 (if the component type is tagged, then we may need to do
620 -- tag adjustments. Perhaps this should be refined to check for any
621 -- component associations that actually need tag adjustment, similar
622 -- to the test in Component_Not_OK_For_Backend for record aggregates
623 -- with tagged components, but not clear whether it's worthwhile ???;
624 -- in the case of the JVM, object tags are handled implicitly)
626 if Is_Tagged_Type (Component_Type (Typ)) and then VM_Target = No_VM then
627 return False;
628 end if;
630 -- Checks 6 (component type must not have bit aligned components)
632 if Type_May_Have_Bit_Aligned_Components (Component_Type (Typ)) then
633 return False;
634 end if;
636 -- Backend processing is possible
638 Set_Size_Known_At_Compile_Time (Etype (N), True);
639 return True;
640 end Backend_Processing_Possible;
642 ---------------------------
643 -- Build_Array_Aggr_Code --
644 ---------------------------
646 -- The code that we generate from a one dimensional aggregate is
648 -- 1. If the sub-aggregate contains discrete choices we
650 -- (a) Sort the discrete choices
652 -- (b) Otherwise for each discrete choice that specifies a range we
653 -- emit a loop. If a range specifies a maximum of three values, or
654 -- we are dealing with an expression we emit a sequence of
655 -- assignments instead of a loop.
657 -- (c) Generate the remaining loops to cover the others choice if any
659 -- 2. If the aggregate contains positional elements we
661 -- (a) translate the positional elements in a series of assignments
663 -- (b) Generate a final loop to cover the others choice if any.
664 -- Note that this final loop has to be a while loop since the case
666 -- L : Integer := Integer'Last;
667 -- H : Integer := Integer'Last;
668 -- A : array (L .. H) := (1, others =>0);
670 -- cannot be handled by a for loop. Thus for the following
672 -- array (L .. H) := (.. positional elements.., others =>E);
674 -- we always generate something like:
676 -- J : Index_Type := Index_Of_Last_Positional_Element;
677 -- while J < H loop
678 -- J := Index_Base'Succ (J)
679 -- Tmp (J) := E;
680 -- end loop;
682 function Build_Array_Aggr_Code
683 (N : Node_Id;
684 Ctype : Entity_Id;
685 Index : Node_Id;
686 Into : Node_Id;
687 Scalar_Comp : Boolean;
688 Indices : List_Id := No_List;
689 Flist : Node_Id := Empty) return List_Id
691 Loc : constant Source_Ptr := Sloc (N);
692 Index_Base : constant Entity_Id := Base_Type (Etype (Index));
693 Index_Base_L : constant Node_Id := Type_Low_Bound (Index_Base);
694 Index_Base_H : constant Node_Id := Type_High_Bound (Index_Base);
696 function Add (Val : Int; To : Node_Id) return Node_Id;
697 -- Returns an expression where Val is added to expression To, unless
698 -- To+Val is provably out of To's base type range. To must be an
699 -- already analyzed expression.
701 function Empty_Range (L, H : Node_Id) return Boolean;
702 -- Returns True if the range defined by L .. H is certainly empty
704 function Equal (L, H : Node_Id) return Boolean;
705 -- Returns True if L = H for sure
707 function Index_Base_Name return Node_Id;
708 -- Returns a new reference to the index type name
710 function Gen_Assign (Ind : Node_Id; Expr : Node_Id) return List_Id;
711 -- Ind must be a side-effect free expression. If the input aggregate
712 -- N to Build_Loop contains no sub-aggregates, then this function
713 -- returns the assignment statement:
715 -- Into (Indices, Ind) := Expr;
717 -- Otherwise we call Build_Code recursively
719 -- Ada 2005 (AI-287): In case of default initialized component, Expr
720 -- is empty and we generate a call to the corresponding IP subprogram.
722 function Gen_Loop (L, H : Node_Id; Expr : Node_Id) return List_Id;
723 -- Nodes L and H must be side-effect free expressions.
724 -- If the input aggregate N to Build_Loop contains no sub-aggregates,
725 -- This routine returns the for loop statement
727 -- for J in Index_Base'(L) .. Index_Base'(H) loop
728 -- Into (Indices, J) := Expr;
729 -- end loop;
731 -- Otherwise we call Build_Code recursively.
732 -- As an optimization if the loop covers 3 or less scalar elements we
733 -- generate a sequence of assignments.
735 function Gen_While (L, H : Node_Id; Expr : Node_Id) return List_Id;
736 -- Nodes L and H must be side-effect free expressions.
737 -- If the input aggregate N to Build_Loop contains no sub-aggregates,
738 -- This routine returns the while loop statement
740 -- J : Index_Base := L;
741 -- while J < H loop
742 -- J := Index_Base'Succ (J);
743 -- Into (Indices, J) := Expr;
744 -- end loop;
746 -- Otherwise we call Build_Code recursively
748 function Local_Compile_Time_Known_Value (E : Node_Id) return Boolean;
749 function Local_Expr_Value (E : Node_Id) return Uint;
750 -- These two Local routines are used to replace the corresponding ones
751 -- in sem_eval because while processing the bounds of an aggregate with
752 -- discrete choices whose index type is an enumeration, we build static
753 -- expressions not recognized by Compile_Time_Known_Value as such since
754 -- they have not yet been analyzed and resolved. All the expressions in
755 -- question are things like Index_Base_Name'Val (Const) which we can
756 -- easily recognize as being constant.
758 ---------
759 -- Add --
760 ---------
762 function Add (Val : Int; To : Node_Id) return Node_Id is
763 Expr_Pos : Node_Id;
764 Expr : Node_Id;
765 To_Pos : Node_Id;
766 U_To : Uint;
767 U_Val : constant Uint := UI_From_Int (Val);
769 begin
770 -- Note: do not try to optimize the case of Val = 0, because
771 -- we need to build a new node with the proper Sloc value anyway.
773 -- First test if we can do constant folding
775 if Local_Compile_Time_Known_Value (To) then
776 U_To := Local_Expr_Value (To) + Val;
778 -- Determine if our constant is outside the range of the index.
779 -- If so return an Empty node. This empty node will be caught
780 -- by Empty_Range below.
782 if Compile_Time_Known_Value (Index_Base_L)
783 and then U_To < Expr_Value (Index_Base_L)
784 then
785 return Empty;
787 elsif Compile_Time_Known_Value (Index_Base_H)
788 and then U_To > Expr_Value (Index_Base_H)
789 then
790 return Empty;
791 end if;
793 Expr_Pos := Make_Integer_Literal (Loc, U_To);
794 Set_Is_Static_Expression (Expr_Pos);
796 if not Is_Enumeration_Type (Index_Base) then
797 Expr := Expr_Pos;
799 -- If we are dealing with enumeration return
800 -- Index_Base'Val (Expr_Pos)
802 else
803 Expr :=
804 Make_Attribute_Reference
805 (Loc,
806 Prefix => Index_Base_Name,
807 Attribute_Name => Name_Val,
808 Expressions => New_List (Expr_Pos));
809 end if;
811 return Expr;
812 end if;
814 -- If we are here no constant folding possible
816 if not Is_Enumeration_Type (Index_Base) then
817 Expr :=
818 Make_Op_Add (Loc,
819 Left_Opnd => Duplicate_Subexpr (To),
820 Right_Opnd => Make_Integer_Literal (Loc, U_Val));
822 -- If we are dealing with enumeration return
823 -- Index_Base'Val (Index_Base'Pos (To) + Val)
825 else
826 To_Pos :=
827 Make_Attribute_Reference
828 (Loc,
829 Prefix => Index_Base_Name,
830 Attribute_Name => Name_Pos,
831 Expressions => New_List (Duplicate_Subexpr (To)));
833 Expr_Pos :=
834 Make_Op_Add (Loc,
835 Left_Opnd => To_Pos,
836 Right_Opnd => Make_Integer_Literal (Loc, U_Val));
838 Expr :=
839 Make_Attribute_Reference
840 (Loc,
841 Prefix => Index_Base_Name,
842 Attribute_Name => Name_Val,
843 Expressions => New_List (Expr_Pos));
844 end if;
846 return Expr;
847 end Add;
849 -----------------
850 -- Empty_Range --
851 -----------------
853 function Empty_Range (L, H : Node_Id) return Boolean is
854 Is_Empty : Boolean := False;
855 Low : Node_Id;
856 High : Node_Id;
858 begin
859 -- First check if L or H were already detected as overflowing the
860 -- index base range type by function Add above. If this is so Add
861 -- returns the empty node.
863 if No (L) or else No (H) then
864 return True;
865 end if;
867 for J in 1 .. 3 loop
868 case J is
870 -- L > H range is empty
872 when 1 =>
873 Low := L;
874 High := H;
876 -- B_L > H range must be empty
878 when 2 =>
879 Low := Index_Base_L;
880 High := H;
882 -- L > B_H range must be empty
884 when 3 =>
885 Low := L;
886 High := Index_Base_H;
887 end case;
889 if Local_Compile_Time_Known_Value (Low)
890 and then Local_Compile_Time_Known_Value (High)
891 then
892 Is_Empty :=
893 UI_Gt (Local_Expr_Value (Low), Local_Expr_Value (High));
894 end if;
896 exit when Is_Empty;
897 end loop;
899 return Is_Empty;
900 end Empty_Range;
902 -----------
903 -- Equal --
904 -----------
906 function Equal (L, H : Node_Id) return Boolean is
907 begin
908 if L = H then
909 return True;
911 elsif Local_Compile_Time_Known_Value (L)
912 and then Local_Compile_Time_Known_Value (H)
913 then
914 return UI_Eq (Local_Expr_Value (L), Local_Expr_Value (H));
915 end if;
917 return False;
918 end Equal;
920 ----------------
921 -- Gen_Assign --
922 ----------------
924 function Gen_Assign (Ind : Node_Id; Expr : Node_Id) return List_Id is
925 L : constant List_Id := New_List;
926 F : Entity_Id;
927 A : Node_Id;
929 New_Indices : List_Id;
930 Indexed_Comp : Node_Id;
931 Expr_Q : Node_Id;
932 Comp_Type : Entity_Id := Empty;
934 function Add_Loop_Actions (Lis : List_Id) return List_Id;
935 -- Collect insert_actions generated in the construction of a
936 -- loop, and prepend them to the sequence of assignments to
937 -- complete the eventual body of the loop.
939 ----------------------
940 -- Add_Loop_Actions --
941 ----------------------
943 function Add_Loop_Actions (Lis : List_Id) return List_Id is
944 Res : List_Id;
946 begin
947 -- Ada 2005 (AI-287): Do nothing else in case of default
948 -- initialized component.
950 if No (Expr) then
951 return Lis;
953 elsif Nkind (Parent (Expr)) = N_Component_Association
954 and then Present (Loop_Actions (Parent (Expr)))
955 then
956 Append_List (Lis, Loop_Actions (Parent (Expr)));
957 Res := Loop_Actions (Parent (Expr));
958 Set_Loop_Actions (Parent (Expr), No_List);
959 return Res;
961 else
962 return Lis;
963 end if;
964 end Add_Loop_Actions;
966 -- Start of processing for Gen_Assign
968 begin
969 if No (Indices) then
970 New_Indices := New_List;
971 else
972 New_Indices := New_Copy_List_Tree (Indices);
973 end if;
975 Append_To (New_Indices, Ind);
977 if Present (Flist) then
978 F := New_Copy_Tree (Flist);
980 elsif Present (Etype (N)) and then Needs_Finalization (Etype (N)) then
981 if Is_Entity_Name (Into)
982 and then Present (Scope (Entity (Into)))
983 then
984 F := Find_Final_List (Scope (Entity (Into)));
985 else
986 F := Find_Final_List (Current_Scope);
987 end if;
988 else
989 F := Empty;
990 end if;
992 if Present (Next_Index (Index)) then
993 return
994 Add_Loop_Actions (
995 Build_Array_Aggr_Code
996 (N => Expr,
997 Ctype => Ctype,
998 Index => Next_Index (Index),
999 Into => Into,
1000 Scalar_Comp => Scalar_Comp,
1001 Indices => New_Indices,
1002 Flist => F));
1003 end if;
1005 -- If we get here then we are at a bottom-level (sub-)aggregate
1007 Indexed_Comp :=
1008 Checks_Off
1009 (Make_Indexed_Component (Loc,
1010 Prefix => New_Copy_Tree (Into),
1011 Expressions => New_Indices));
1013 Set_Assignment_OK (Indexed_Comp);
1015 -- Ada 2005 (AI-287): In case of default initialized component, Expr
1016 -- is not present (and therefore we also initialize Expr_Q to empty).
1018 if No (Expr) then
1019 Expr_Q := Empty;
1020 elsif Nkind (Expr) = N_Qualified_Expression then
1021 Expr_Q := Expression (Expr);
1022 else
1023 Expr_Q := Expr;
1024 end if;
1026 if Present (Etype (N))
1027 and then Etype (N) /= Any_Composite
1028 then
1029 Comp_Type := Component_Type (Etype (N));
1030 pragma Assert (Comp_Type = Ctype); -- AI-287
1032 elsif Present (Next (First (New_Indices))) then
1034 -- Ada 2005 (AI-287): Do nothing in case of default initialized
1035 -- component because we have received the component type in
1036 -- the formal parameter Ctype.
1038 -- ??? Some assert pragmas have been added to check if this new
1039 -- formal can be used to replace this code in all cases.
1041 if Present (Expr) then
1043 -- This is a multidimensional array. Recover the component
1044 -- type from the outermost aggregate, because subaggregates
1045 -- do not have an assigned type.
1047 declare
1048 P : Node_Id;
1050 begin
1051 P := Parent (Expr);
1052 while Present (P) loop
1053 if Nkind (P) = N_Aggregate
1054 and then Present (Etype (P))
1055 then
1056 Comp_Type := Component_Type (Etype (P));
1057 exit;
1059 else
1060 P := Parent (P);
1061 end if;
1062 end loop;
1064 pragma Assert (Comp_Type = Ctype); -- AI-287
1065 end;
1066 end if;
1067 end if;
1069 -- Ada 2005 (AI-287): We only analyze the expression in case of non-
1070 -- default initialized components (otherwise Expr_Q is not present).
1072 if Present (Expr_Q)
1073 and then Nkind_In (Expr_Q, N_Aggregate, N_Extension_Aggregate)
1074 then
1075 -- At this stage the Expression may not have been analyzed yet
1076 -- because the array aggregate code has not been updated to use
1077 -- the Expansion_Delayed flag and avoid analysis altogether to
1078 -- solve the same problem (see Resolve_Aggr_Expr). So let us do
1079 -- the analysis of non-array aggregates now in order to get the
1080 -- value of Expansion_Delayed flag for the inner aggregate ???
1082 if Present (Comp_Type) and then not Is_Array_Type (Comp_Type) then
1083 Analyze_And_Resolve (Expr_Q, Comp_Type);
1084 end if;
1086 if Is_Delayed_Aggregate (Expr_Q) then
1088 -- This is either a subaggregate of a multidimentional array,
1089 -- or a component of an array type whose component type is
1090 -- also an array. In the latter case, the expression may have
1091 -- component associations that provide different bounds from
1092 -- those of the component type, and sliding must occur. Instead
1093 -- of decomposing the current aggregate assignment, force the
1094 -- re-analysis of the assignment, so that a temporary will be
1095 -- generated in the usual fashion, and sliding will take place.
1097 if Nkind (Parent (N)) = N_Assignment_Statement
1098 and then Is_Array_Type (Comp_Type)
1099 and then Present (Component_Associations (Expr_Q))
1100 and then Must_Slide (Comp_Type, Etype (Expr_Q))
1101 then
1102 Set_Expansion_Delayed (Expr_Q, False);
1103 Set_Analyzed (Expr_Q, False);
1105 else
1106 return
1107 Add_Loop_Actions (
1108 Late_Expansion (
1109 Expr_Q, Etype (Expr_Q), Indexed_Comp, F));
1110 end if;
1111 end if;
1112 end if;
1114 -- Ada 2005 (AI-287): In case of default initialized component, call
1115 -- the initialization subprogram associated with the component type.
1116 -- If the component type is an access type, add an explicit null
1117 -- assignment, because for the back-end there is an initialization
1118 -- present for the whole aggregate, and no default initialization
1119 -- will take place.
1121 -- In addition, if the component type is controlled, we must call
1122 -- its Initialize procedure explicitly, because there is no explicit
1123 -- object creation that will invoke it otherwise.
1125 if No (Expr) then
1126 if Present (Base_Init_Proc (Base_Type (Ctype)))
1127 or else Has_Task (Base_Type (Ctype))
1128 then
1129 Append_List_To (L,
1130 Build_Initialization_Call (Loc,
1131 Id_Ref => Indexed_Comp,
1132 Typ => Ctype,
1133 With_Default_Init => True));
1135 elsif Is_Access_Type (Ctype) then
1136 Append_To (L,
1137 Make_Assignment_Statement (Loc,
1138 Name => Indexed_Comp,
1139 Expression => Make_Null (Loc)));
1140 end if;
1142 if Needs_Finalization (Ctype) then
1143 Append_List_To (L,
1144 Make_Init_Call (
1145 Ref => New_Copy_Tree (Indexed_Comp),
1146 Typ => Ctype,
1147 Flist_Ref => Find_Final_List (Current_Scope),
1148 With_Attach => Make_Integer_Literal (Loc, 1)));
1149 end if;
1151 else
1152 -- Now generate the assignment with no associated controlled
1153 -- actions since the target of the assignment may not have been
1154 -- initialized, it is not possible to Finalize it as expected by
1155 -- normal controlled assignment. The rest of the controlled
1156 -- actions are done manually with the proper finalization list
1157 -- coming from the context.
1159 A :=
1160 Make_OK_Assignment_Statement (Loc,
1161 Name => Indexed_Comp,
1162 Expression => New_Copy_Tree (Expr));
1164 if Present (Comp_Type) and then Needs_Finalization (Comp_Type) then
1165 Set_No_Ctrl_Actions (A);
1167 -- If this is an aggregate for an array of arrays, each
1168 -- sub-aggregate will be expanded as well, and even with
1169 -- No_Ctrl_Actions the assignments of inner components will
1170 -- require attachment in their assignments to temporaries.
1171 -- These temporaries must be finalized for each subaggregate,
1172 -- to prevent multiple attachments of the same temporary
1173 -- location to same finalization chain (and consequently
1174 -- circular lists). To ensure that finalization takes place
1175 -- for each subaggregate we wrap the assignment in a block.
1177 if Is_Array_Type (Comp_Type)
1178 and then Nkind (Expr) = N_Aggregate
1179 then
1180 A :=
1181 Make_Block_Statement (Loc,
1182 Handled_Statement_Sequence =>
1183 Make_Handled_Sequence_Of_Statements (Loc,
1184 Statements => New_List (A)));
1185 end if;
1186 end if;
1188 Append_To (L, A);
1190 -- Adjust the tag if tagged (because of possible view
1191 -- conversions), unless compiling for the Java VM where
1192 -- tags are implicit.
1194 if Present (Comp_Type)
1195 and then Is_Tagged_Type (Comp_Type)
1196 and then VM_Target = No_VM
1197 then
1198 A :=
1199 Make_OK_Assignment_Statement (Loc,
1200 Name =>
1201 Make_Selected_Component (Loc,
1202 Prefix => New_Copy_Tree (Indexed_Comp),
1203 Selector_Name =>
1204 New_Reference_To
1205 (First_Tag_Component (Comp_Type), Loc)),
1207 Expression =>
1208 Unchecked_Convert_To (RTE (RE_Tag),
1209 New_Reference_To
1210 (Node (First_Elmt (Access_Disp_Table (Comp_Type))),
1211 Loc)));
1213 Append_To (L, A);
1214 end if;
1216 -- Adjust and attach the component to the proper final list, which
1217 -- can be the controller of the outer record object or the final
1218 -- list associated with the scope.
1220 -- If the component is itself an array of controlled types, whose
1221 -- value is given by a sub-aggregate, then the attach calls have
1222 -- been generated when individual subcomponent are assigned, and
1223 -- must not be done again to prevent malformed finalization chains
1224 -- (see comments above, concerning the creation of a block to hold
1225 -- inner finalization actions).
1227 if Present (Comp_Type)
1228 and then Needs_Finalization (Comp_Type)
1229 and then not Is_Limited_Type (Comp_Type)
1230 and then not
1231 (Is_Array_Type (Comp_Type)
1232 and then Is_Controlled (Component_Type (Comp_Type))
1233 and then Nkind (Expr) = N_Aggregate)
1234 then
1235 Append_List_To (L,
1236 Make_Adjust_Call (
1237 Ref => New_Copy_Tree (Indexed_Comp),
1238 Typ => Comp_Type,
1239 Flist_Ref => F,
1240 With_Attach => Make_Integer_Literal (Loc, 1)));
1241 end if;
1242 end if;
1244 return Add_Loop_Actions (L);
1245 end Gen_Assign;
1247 --------------
1248 -- Gen_Loop --
1249 --------------
1251 function Gen_Loop (L, H : Node_Id; Expr : Node_Id) return List_Id is
1252 L_J : Node_Id;
1254 L_Range : Node_Id;
1255 -- Index_Base'(L) .. Index_Base'(H)
1257 L_Iteration_Scheme : Node_Id;
1258 -- L_J in Index_Base'(L) .. Index_Base'(H)
1260 L_Body : List_Id;
1261 -- The statements to execute in the loop
1263 S : constant List_Id := New_List;
1264 -- List of statements
1266 Tcopy : Node_Id;
1267 -- Copy of expression tree, used for checking purposes
1269 begin
1270 -- If loop bounds define an empty range return the null statement
1272 if Empty_Range (L, H) then
1273 Append_To (S, Make_Null_Statement (Loc));
1275 -- Ada 2005 (AI-287): Nothing else need to be done in case of
1276 -- default initialized component.
1278 if No (Expr) then
1279 null;
1281 else
1282 -- The expression must be type-checked even though no component
1283 -- of the aggregate will have this value. This is done only for
1284 -- actual components of the array, not for subaggregates. Do
1285 -- the check on a copy, because the expression may be shared
1286 -- among several choices, some of which might be non-null.
1288 if Present (Etype (N))
1289 and then Is_Array_Type (Etype (N))
1290 and then No (Next_Index (Index))
1291 then
1292 Expander_Mode_Save_And_Set (False);
1293 Tcopy := New_Copy_Tree (Expr);
1294 Set_Parent (Tcopy, N);
1295 Analyze_And_Resolve (Tcopy, Component_Type (Etype (N)));
1296 Expander_Mode_Restore;
1297 end if;
1298 end if;
1300 return S;
1302 -- If loop bounds are the same then generate an assignment
1304 elsif Equal (L, H) then
1305 return Gen_Assign (New_Copy_Tree (L), Expr);
1307 -- If H - L <= 2 then generate a sequence of assignments when we are
1308 -- processing the bottom most aggregate and it contains scalar
1309 -- components.
1311 elsif No (Next_Index (Index))
1312 and then Scalar_Comp
1313 and then Local_Compile_Time_Known_Value (L)
1314 and then Local_Compile_Time_Known_Value (H)
1315 and then Local_Expr_Value (H) - Local_Expr_Value (L) <= 2
1316 then
1318 Append_List_To (S, Gen_Assign (New_Copy_Tree (L), Expr));
1319 Append_List_To (S, Gen_Assign (Add (1, To => L), Expr));
1321 if Local_Expr_Value (H) - Local_Expr_Value (L) = 2 then
1322 Append_List_To (S, Gen_Assign (Add (2, To => L), Expr));
1323 end if;
1325 return S;
1326 end if;
1328 -- Otherwise construct the loop, starting with the loop index L_J
1330 L_J := Make_Defining_Identifier (Loc, New_Internal_Name ('J'));
1332 -- Construct "L .. H"
1334 L_Range :=
1335 Make_Range
1336 (Loc,
1337 Low_Bound => Make_Qualified_Expression
1338 (Loc,
1339 Subtype_Mark => Index_Base_Name,
1340 Expression => L),
1341 High_Bound => Make_Qualified_Expression
1342 (Loc,
1343 Subtype_Mark => Index_Base_Name,
1344 Expression => H));
1346 -- Construct "for L_J in Index_Base range L .. H"
1348 L_Iteration_Scheme :=
1349 Make_Iteration_Scheme
1350 (Loc,
1351 Loop_Parameter_Specification =>
1352 Make_Loop_Parameter_Specification
1353 (Loc,
1354 Defining_Identifier => L_J,
1355 Discrete_Subtype_Definition => L_Range));
1357 -- Construct the statements to execute in the loop body
1359 L_Body := Gen_Assign (New_Reference_To (L_J, Loc), Expr);
1361 -- Construct the final loop
1363 Append_To (S, Make_Implicit_Loop_Statement
1364 (Node => N,
1365 Identifier => Empty,
1366 Iteration_Scheme => L_Iteration_Scheme,
1367 Statements => L_Body));
1369 -- A small optimization: if the aggregate is initialized with a box
1370 -- and the component type has no initialization procedure, remove the
1371 -- useless empty loop.
1373 if Nkind (First (S)) = N_Loop_Statement
1374 and then Is_Empty_List (Statements (First (S)))
1375 then
1376 return New_List (Make_Null_Statement (Loc));
1377 else
1378 return S;
1379 end if;
1380 end Gen_Loop;
1382 ---------------
1383 -- Gen_While --
1384 ---------------
1386 -- The code built is
1388 -- W_J : Index_Base := L;
1389 -- while W_J < H loop
1390 -- W_J := Index_Base'Succ (W);
1391 -- L_Body;
1392 -- end loop;
1394 function Gen_While (L, H : Node_Id; Expr : Node_Id) return List_Id is
1395 W_J : Node_Id;
1397 W_Decl : Node_Id;
1398 -- W_J : Base_Type := L;
1400 W_Iteration_Scheme : Node_Id;
1401 -- while W_J < H
1403 W_Index_Succ : Node_Id;
1404 -- Index_Base'Succ (J)
1406 W_Increment : Node_Id;
1407 -- W_J := Index_Base'Succ (W)
1409 W_Body : constant List_Id := New_List;
1410 -- The statements to execute in the loop
1412 S : constant List_Id := New_List;
1413 -- list of statement
1415 begin
1416 -- If loop bounds define an empty range or are equal return null
1418 if Empty_Range (L, H) or else Equal (L, H) then
1419 Append_To (S, Make_Null_Statement (Loc));
1420 return S;
1421 end if;
1423 -- Build the decl of W_J
1425 W_J := Make_Defining_Identifier (Loc, New_Internal_Name ('J'));
1426 W_Decl :=
1427 Make_Object_Declaration
1428 (Loc,
1429 Defining_Identifier => W_J,
1430 Object_Definition => Index_Base_Name,
1431 Expression => L);
1433 -- Theoretically we should do a New_Copy_Tree (L) here, but we know
1434 -- that in this particular case L is a fresh Expr generated by
1435 -- Add which we are the only ones to use.
1437 Append_To (S, W_Decl);
1439 -- Construct " while W_J < H"
1441 W_Iteration_Scheme :=
1442 Make_Iteration_Scheme
1443 (Loc,
1444 Condition => Make_Op_Lt
1445 (Loc,
1446 Left_Opnd => New_Reference_To (W_J, Loc),
1447 Right_Opnd => New_Copy_Tree (H)));
1449 -- Construct the statements to execute in the loop body
1451 W_Index_Succ :=
1452 Make_Attribute_Reference
1453 (Loc,
1454 Prefix => Index_Base_Name,
1455 Attribute_Name => Name_Succ,
1456 Expressions => New_List (New_Reference_To (W_J, Loc)));
1458 W_Increment :=
1459 Make_OK_Assignment_Statement
1460 (Loc,
1461 Name => New_Reference_To (W_J, Loc),
1462 Expression => W_Index_Succ);
1464 Append_To (W_Body, W_Increment);
1465 Append_List_To (W_Body,
1466 Gen_Assign (New_Reference_To (W_J, Loc), Expr));
1468 -- Construct the final loop
1470 Append_To (S, Make_Implicit_Loop_Statement
1471 (Node => N,
1472 Identifier => Empty,
1473 Iteration_Scheme => W_Iteration_Scheme,
1474 Statements => W_Body));
1476 return S;
1477 end Gen_While;
1479 ---------------------
1480 -- Index_Base_Name --
1481 ---------------------
1483 function Index_Base_Name return Node_Id is
1484 begin
1485 return New_Reference_To (Index_Base, Sloc (N));
1486 end Index_Base_Name;
1488 ------------------------------------
1489 -- Local_Compile_Time_Known_Value --
1490 ------------------------------------
1492 function Local_Compile_Time_Known_Value (E : Node_Id) return Boolean is
1493 begin
1494 return Compile_Time_Known_Value (E)
1495 or else
1496 (Nkind (E) = N_Attribute_Reference
1497 and then Attribute_Name (E) = Name_Val
1498 and then Compile_Time_Known_Value (First (Expressions (E))));
1499 end Local_Compile_Time_Known_Value;
1501 ----------------------
1502 -- Local_Expr_Value --
1503 ----------------------
1505 function Local_Expr_Value (E : Node_Id) return Uint is
1506 begin
1507 if Compile_Time_Known_Value (E) then
1508 return Expr_Value (E);
1509 else
1510 return Expr_Value (First (Expressions (E)));
1511 end if;
1512 end Local_Expr_Value;
1514 -- Build_Array_Aggr_Code Variables
1516 Assoc : Node_Id;
1517 Choice : Node_Id;
1518 Expr : Node_Id;
1519 Typ : Entity_Id;
1521 Others_Expr : Node_Id := Empty;
1522 Others_Box_Present : Boolean := False;
1524 Aggr_L : constant Node_Id := Low_Bound (Aggregate_Bounds (N));
1525 Aggr_H : constant Node_Id := High_Bound (Aggregate_Bounds (N));
1526 -- The aggregate bounds of this specific sub-aggregate. Note that if
1527 -- the code generated by Build_Array_Aggr_Code is executed then these
1528 -- bounds are OK. Otherwise a Constraint_Error would have been raised.
1530 Aggr_Low : constant Node_Id := Duplicate_Subexpr_No_Checks (Aggr_L);
1531 Aggr_High : constant Node_Id := Duplicate_Subexpr_No_Checks (Aggr_H);
1532 -- After Duplicate_Subexpr these are side-effect free
1534 Low : Node_Id;
1535 High : Node_Id;
1537 Nb_Choices : Nat := 0;
1538 Table : Case_Table_Type (1 .. Number_Of_Choices (N));
1539 -- Used to sort all the different choice values
1541 Nb_Elements : Int;
1542 -- Number of elements in the positional aggregate
1544 New_Code : constant List_Id := New_List;
1546 -- Start of processing for Build_Array_Aggr_Code
1548 begin
1549 -- First before we start, a special case. if we have a bit packed
1550 -- array represented as a modular type, then clear the value to
1551 -- zero first, to ensure that unused bits are properly cleared.
1553 Typ := Etype (N);
1555 if Present (Typ)
1556 and then Is_Bit_Packed_Array (Typ)
1557 and then Is_Modular_Integer_Type (Packed_Array_Type (Typ))
1558 then
1559 Append_To (New_Code,
1560 Make_Assignment_Statement (Loc,
1561 Name => New_Copy_Tree (Into),
1562 Expression =>
1563 Unchecked_Convert_To (Typ,
1564 Make_Integer_Literal (Loc, Uint_0))));
1565 end if;
1567 -- If the component type contains tasks, we need to build a Master
1568 -- entity in the current scope, because it will be needed if build-
1569 -- in-place functions are called in the expanded code.
1571 if Nkind (Parent (N)) = N_Object_Declaration
1572 and then Has_Task (Typ)
1573 then
1574 Build_Master_Entity (Defining_Identifier (Parent (N)));
1575 end if;
1577 -- STEP 1: Process component associations
1579 -- For those associations that may generate a loop, initialize
1580 -- Loop_Actions to collect inserted actions that may be crated.
1582 -- Skip this if no component associations
1584 if No (Expressions (N)) then
1586 -- STEP 1 (a): Sort the discrete choices
1588 Assoc := First (Component_Associations (N));
1589 while Present (Assoc) loop
1590 Choice := First (Choices (Assoc));
1591 while Present (Choice) loop
1592 if Nkind (Choice) = N_Others_Choice then
1593 Set_Loop_Actions (Assoc, New_List);
1595 if Box_Present (Assoc) then
1596 Others_Box_Present := True;
1597 else
1598 Others_Expr := Expression (Assoc);
1599 end if;
1600 exit;
1601 end if;
1603 Get_Index_Bounds (Choice, Low, High);
1605 if Low /= High then
1606 Set_Loop_Actions (Assoc, New_List);
1607 end if;
1609 Nb_Choices := Nb_Choices + 1;
1610 if Box_Present (Assoc) then
1611 Table (Nb_Choices) := (Choice_Lo => Low,
1612 Choice_Hi => High,
1613 Choice_Node => Empty);
1614 else
1615 Table (Nb_Choices) := (Choice_Lo => Low,
1616 Choice_Hi => High,
1617 Choice_Node => Expression (Assoc));
1618 end if;
1619 Next (Choice);
1620 end loop;
1622 Next (Assoc);
1623 end loop;
1625 -- If there is more than one set of choices these must be static
1626 -- and we can therefore sort them. Remember that Nb_Choices does not
1627 -- account for an others choice.
1629 if Nb_Choices > 1 then
1630 Sort_Case_Table (Table);
1631 end if;
1633 -- STEP 1 (b): take care of the whole set of discrete choices
1635 for J in 1 .. Nb_Choices loop
1636 Low := Table (J).Choice_Lo;
1637 High := Table (J).Choice_Hi;
1638 Expr := Table (J).Choice_Node;
1639 Append_List (Gen_Loop (Low, High, Expr), To => New_Code);
1640 end loop;
1642 -- STEP 1 (c): generate the remaining loops to cover others choice
1643 -- We don't need to generate loops over empty gaps, but if there is
1644 -- a single empty range we must analyze the expression for semantics
1646 if Present (Others_Expr) or else Others_Box_Present then
1647 declare
1648 First : Boolean := True;
1650 begin
1651 for J in 0 .. Nb_Choices loop
1652 if J = 0 then
1653 Low := Aggr_Low;
1654 else
1655 Low := Add (1, To => Table (J).Choice_Hi);
1656 end if;
1658 if J = Nb_Choices then
1659 High := Aggr_High;
1660 else
1661 High := Add (-1, To => Table (J + 1).Choice_Lo);
1662 end if;
1664 -- If this is an expansion within an init proc, make
1665 -- sure that discriminant references are replaced by
1666 -- the corresponding discriminal.
1668 if Inside_Init_Proc then
1669 if Is_Entity_Name (Low)
1670 and then Ekind (Entity (Low)) = E_Discriminant
1671 then
1672 Set_Entity (Low, Discriminal (Entity (Low)));
1673 end if;
1675 if Is_Entity_Name (High)
1676 and then Ekind (Entity (High)) = E_Discriminant
1677 then
1678 Set_Entity (High, Discriminal (Entity (High)));
1679 end if;
1680 end if;
1682 if First
1683 or else not Empty_Range (Low, High)
1684 then
1685 First := False;
1686 Append_List
1687 (Gen_Loop (Low, High, Others_Expr), To => New_Code);
1688 end if;
1689 end loop;
1690 end;
1691 end if;
1693 -- STEP 2: Process positional components
1695 else
1696 -- STEP 2 (a): Generate the assignments for each positional element
1697 -- Note that here we have to use Aggr_L rather than Aggr_Low because
1698 -- Aggr_L is analyzed and Add wants an analyzed expression.
1700 Expr := First (Expressions (N));
1701 Nb_Elements := -1;
1702 while Present (Expr) loop
1703 Nb_Elements := Nb_Elements + 1;
1704 Append_List (Gen_Assign (Add (Nb_Elements, To => Aggr_L), Expr),
1705 To => New_Code);
1706 Next (Expr);
1707 end loop;
1709 -- STEP 2 (b): Generate final loop if an others choice is present
1710 -- Here Nb_Elements gives the offset of the last positional element.
1712 if Present (Component_Associations (N)) then
1713 Assoc := Last (Component_Associations (N));
1715 -- Ada 2005 (AI-287)
1717 if Box_Present (Assoc) then
1718 Append_List (Gen_While (Add (Nb_Elements, To => Aggr_L),
1719 Aggr_High,
1720 Empty),
1721 To => New_Code);
1722 else
1723 Expr := Expression (Assoc);
1725 Append_List (Gen_While (Add (Nb_Elements, To => Aggr_L),
1726 Aggr_High,
1727 Expr), -- AI-287
1728 To => New_Code);
1729 end if;
1730 end if;
1731 end if;
1733 return New_Code;
1734 end Build_Array_Aggr_Code;
1736 ----------------------------
1737 -- Build_Record_Aggr_Code --
1738 ----------------------------
1740 function Build_Record_Aggr_Code
1741 (N : Node_Id;
1742 Typ : Entity_Id;
1743 Lhs : Node_Id;
1744 Flist : Node_Id := Empty;
1745 Obj : Entity_Id := Empty;
1746 Is_Limited_Ancestor_Expansion : Boolean := False) return List_Id
1748 Loc : constant Source_Ptr := Sloc (N);
1749 L : constant List_Id := New_List;
1750 N_Typ : constant Entity_Id := Etype (N);
1752 Comp : Node_Id;
1753 Instr : Node_Id;
1754 Ref : Node_Id;
1755 Target : Entity_Id;
1756 F : Node_Id;
1757 Comp_Type : Entity_Id;
1758 Selector : Entity_Id;
1759 Comp_Expr : Node_Id;
1760 Expr_Q : Node_Id;
1762 Internal_Final_List : Node_Id := Empty;
1764 -- If this is an internal aggregate, the External_Final_List is an
1765 -- expression for the controller record of the enclosing type.
1767 -- If the current aggregate has several controlled components, this
1768 -- expression will appear in several calls to attach to the finali-
1769 -- zation list, and it must not be shared.
1771 External_Final_List : Node_Id;
1772 Ancestor_Is_Expression : Boolean := False;
1773 Ancestor_Is_Subtype_Mark : Boolean := False;
1775 Init_Typ : Entity_Id := Empty;
1776 Attach : Node_Id;
1778 Ctrl_Stuff_Done : Boolean := False;
1779 -- True if Gen_Ctrl_Actions_For_Aggr has already been called; calls
1780 -- after the first do nothing.
1782 function Ancestor_Discriminant_Value (Disc : Entity_Id) return Node_Id;
1783 -- Returns the value that the given discriminant of an ancestor type
1784 -- should receive (in the absence of a conflict with the value provided
1785 -- by an ancestor part of an extension aggregate).
1787 procedure Check_Ancestor_Discriminants (Anc_Typ : Entity_Id);
1788 -- Check that each of the discriminant values defined by the ancestor
1789 -- part of an extension aggregate match the corresponding values
1790 -- provided by either an association of the aggregate or by the
1791 -- constraint imposed by a parent type (RM95-4.3.2(8)).
1793 function Compatible_Int_Bounds
1794 (Agg_Bounds : Node_Id;
1795 Typ_Bounds : Node_Id) return Boolean;
1796 -- Return true if Agg_Bounds are equal or within Typ_Bounds. It is
1797 -- assumed that both bounds are integer ranges.
1799 procedure Gen_Ctrl_Actions_For_Aggr;
1800 -- Deal with the various controlled type data structure initializations
1801 -- (but only if it hasn't been done already).
1803 function Get_Constraint_Association (T : Entity_Id) return Node_Id;
1804 -- Returns the first discriminant association in the constraint
1805 -- associated with T, if any, otherwise returns Empty.
1807 function Init_Controller
1808 (Target : Node_Id;
1809 Typ : Entity_Id;
1810 F : Node_Id;
1811 Attach : Node_Id;
1812 Init_Pr : Boolean) return List_Id;
1813 -- Returns the list of statements necessary to initialize the internal
1814 -- controller of the (possible) ancestor typ into target and attach it
1815 -- to finalization list F. Init_Pr conditions the call to the init proc
1816 -- since it may already be done due to ancestor initialization.
1818 function Is_Int_Range_Bounds (Bounds : Node_Id) return Boolean;
1819 -- Check whether Bounds is a range node and its lower and higher bounds
1820 -- are integers literals.
1822 ---------------------------------
1823 -- Ancestor_Discriminant_Value --
1824 ---------------------------------
1826 function Ancestor_Discriminant_Value (Disc : Entity_Id) return Node_Id is
1827 Assoc : Node_Id;
1828 Assoc_Elmt : Elmt_Id;
1829 Aggr_Comp : Entity_Id;
1830 Corresp_Disc : Entity_Id;
1831 Current_Typ : Entity_Id := Base_Type (Typ);
1832 Parent_Typ : Entity_Id;
1833 Parent_Disc : Entity_Id;
1834 Save_Assoc : Node_Id := Empty;
1836 begin
1837 -- First check any discriminant associations to see if any of them
1838 -- provide a value for the discriminant.
1840 if Present (Discriminant_Specifications (Parent (Current_Typ))) then
1841 Assoc := First (Component_Associations (N));
1842 while Present (Assoc) loop
1843 Aggr_Comp := Entity (First (Choices (Assoc)));
1845 if Ekind (Aggr_Comp) = E_Discriminant then
1846 Save_Assoc := Expression (Assoc);
1848 Corresp_Disc := Corresponding_Discriminant (Aggr_Comp);
1849 while Present (Corresp_Disc) loop
1851 -- If found a corresponding discriminant then return the
1852 -- value given in the aggregate. (Note: this is not
1853 -- correct in the presence of side effects. ???)
1855 if Disc = Corresp_Disc then
1856 return Duplicate_Subexpr (Expression (Assoc));
1857 end if;
1859 Corresp_Disc :=
1860 Corresponding_Discriminant (Corresp_Disc);
1861 end loop;
1862 end if;
1864 Next (Assoc);
1865 end loop;
1866 end if;
1868 -- No match found in aggregate, so chain up parent types to find
1869 -- a constraint that defines the value of the discriminant.
1871 Parent_Typ := Etype (Current_Typ);
1872 while Current_Typ /= Parent_Typ loop
1873 if Has_Discriminants (Parent_Typ)
1874 and then not Has_Unknown_Discriminants (Parent_Typ)
1875 then
1876 Parent_Disc := First_Discriminant (Parent_Typ);
1878 -- We either get the association from the subtype indication
1879 -- of the type definition itself, or from the discriminant
1880 -- constraint associated with the type entity (which is
1881 -- preferable, but it's not always present ???)
1883 if Is_Empty_Elmt_List (
1884 Discriminant_Constraint (Current_Typ))
1885 then
1886 Assoc := Get_Constraint_Association (Current_Typ);
1887 Assoc_Elmt := No_Elmt;
1888 else
1889 Assoc_Elmt :=
1890 First_Elmt (Discriminant_Constraint (Current_Typ));
1891 Assoc := Node (Assoc_Elmt);
1892 end if;
1894 -- Traverse the discriminants of the parent type looking
1895 -- for one that corresponds.
1897 while Present (Parent_Disc) and then Present (Assoc) loop
1898 Corresp_Disc := Parent_Disc;
1899 while Present (Corresp_Disc)
1900 and then Disc /= Corresp_Disc
1901 loop
1902 Corresp_Disc :=
1903 Corresponding_Discriminant (Corresp_Disc);
1904 end loop;
1906 if Disc = Corresp_Disc then
1907 if Nkind (Assoc) = N_Discriminant_Association then
1908 Assoc := Expression (Assoc);
1909 end if;
1911 -- If the located association directly denotes a
1912 -- discriminant, then use the value of a saved
1913 -- association of the aggregate. This is a kludge to
1914 -- handle certain cases involving multiple discriminants
1915 -- mapped to a single discriminant of a descendant. It's
1916 -- not clear how to locate the appropriate discriminant
1917 -- value for such cases. ???
1919 if Is_Entity_Name (Assoc)
1920 and then Ekind (Entity (Assoc)) = E_Discriminant
1921 then
1922 Assoc := Save_Assoc;
1923 end if;
1925 return Duplicate_Subexpr (Assoc);
1926 end if;
1928 Next_Discriminant (Parent_Disc);
1930 if No (Assoc_Elmt) then
1931 Next (Assoc);
1932 else
1933 Next_Elmt (Assoc_Elmt);
1934 if Present (Assoc_Elmt) then
1935 Assoc := Node (Assoc_Elmt);
1936 else
1937 Assoc := Empty;
1938 end if;
1939 end if;
1940 end loop;
1941 end if;
1943 Current_Typ := Parent_Typ;
1944 Parent_Typ := Etype (Current_Typ);
1945 end loop;
1947 -- In some cases there's no ancestor value to locate (such as
1948 -- when an ancestor part given by an expression defines the
1949 -- discriminant value).
1951 return Empty;
1952 end Ancestor_Discriminant_Value;
1954 ----------------------------------
1955 -- Check_Ancestor_Discriminants --
1956 ----------------------------------
1958 procedure Check_Ancestor_Discriminants (Anc_Typ : Entity_Id) is
1959 Discr : Entity_Id;
1960 Disc_Value : Node_Id;
1961 Cond : Node_Id;
1963 begin
1964 Discr := First_Discriminant (Base_Type (Anc_Typ));
1965 while Present (Discr) loop
1966 Disc_Value := Ancestor_Discriminant_Value (Discr);
1968 if Present (Disc_Value) then
1969 Cond := Make_Op_Ne (Loc,
1970 Left_Opnd =>
1971 Make_Selected_Component (Loc,
1972 Prefix => New_Copy_Tree (Target),
1973 Selector_Name => New_Occurrence_Of (Discr, Loc)),
1974 Right_Opnd => Disc_Value);
1976 Append_To (L,
1977 Make_Raise_Constraint_Error (Loc,
1978 Condition => Cond,
1979 Reason => CE_Discriminant_Check_Failed));
1980 end if;
1982 Next_Discriminant (Discr);
1983 end loop;
1984 end Check_Ancestor_Discriminants;
1986 ---------------------------
1987 -- Compatible_Int_Bounds --
1988 ---------------------------
1990 function Compatible_Int_Bounds
1991 (Agg_Bounds : Node_Id;
1992 Typ_Bounds : Node_Id) return Boolean
1994 Agg_Lo : constant Uint := Intval (Low_Bound (Agg_Bounds));
1995 Agg_Hi : constant Uint := Intval (High_Bound (Agg_Bounds));
1996 Typ_Lo : constant Uint := Intval (Low_Bound (Typ_Bounds));
1997 Typ_Hi : constant Uint := Intval (High_Bound (Typ_Bounds));
1998 begin
1999 return Typ_Lo <= Agg_Lo and then Agg_Hi <= Typ_Hi;
2000 end Compatible_Int_Bounds;
2002 --------------------------------
2003 -- Get_Constraint_Association --
2004 --------------------------------
2006 function Get_Constraint_Association (T : Entity_Id) return Node_Id is
2007 Typ_Def : constant Node_Id := Type_Definition (Parent (T));
2008 Indic : constant Node_Id := Subtype_Indication (Typ_Def);
2010 begin
2011 -- ??? Also need to cover case of a type mark denoting a subtype
2012 -- with constraint.
2014 if Nkind (Indic) = N_Subtype_Indication
2015 and then Present (Constraint (Indic))
2016 then
2017 return First (Constraints (Constraint (Indic)));
2018 end if;
2020 return Empty;
2021 end Get_Constraint_Association;
2023 ---------------------
2024 -- Init_Controller --
2025 ---------------------
2027 function Init_Controller
2028 (Target : Node_Id;
2029 Typ : Entity_Id;
2030 F : Node_Id;
2031 Attach : Node_Id;
2032 Init_Pr : Boolean) return List_Id
2034 L : constant List_Id := New_List;
2035 Ref : Node_Id;
2036 RC : RE_Id;
2037 Target_Type : Entity_Id;
2039 begin
2040 -- Generate:
2041 -- init-proc (target._controller);
2042 -- initialize (target._controller);
2043 -- Attach_to_Final_List (target._controller, F);
2045 Ref :=
2046 Make_Selected_Component (Loc,
2047 Prefix => Convert_To (Typ, New_Copy_Tree (Target)),
2048 Selector_Name => Make_Identifier (Loc, Name_uController));
2049 Set_Assignment_OK (Ref);
2051 -- Ada 2005 (AI-287): Give support to aggregates of limited types.
2052 -- If the type is intrinsically limited the controller is limited as
2053 -- well. If it is tagged and limited then so is the controller.
2054 -- Otherwise an untagged type may have limited components without its
2055 -- full view being limited, so the controller is not limited.
2057 if Nkind (Target) = N_Identifier then
2058 Target_Type := Etype (Target);
2060 elsif Nkind (Target) = N_Selected_Component then
2061 Target_Type := Etype (Selector_Name (Target));
2063 elsif Nkind (Target) = N_Unchecked_Type_Conversion then
2064 Target_Type := Etype (Target);
2066 elsif Nkind (Target) = N_Unchecked_Expression
2067 and then Nkind (Expression (Target)) = N_Indexed_Component
2068 then
2069 Target_Type := Etype (Prefix (Expression (Target)));
2071 else
2072 Target_Type := Etype (Target);
2073 end if;
2075 -- If the target has not been analyzed yet, as will happen with
2076 -- delayed expansion, use the given type (either the aggregate type
2077 -- or an ancestor) to determine limitedness.
2079 if No (Target_Type) then
2080 Target_Type := Typ;
2081 end if;
2083 if (Is_Tagged_Type (Target_Type))
2084 and then Is_Limited_Type (Target_Type)
2085 then
2086 RC := RE_Limited_Record_Controller;
2088 elsif Is_Inherently_Limited_Type (Target_Type) then
2089 RC := RE_Limited_Record_Controller;
2091 else
2092 RC := RE_Record_Controller;
2093 end if;
2095 if Init_Pr then
2096 Append_List_To (L,
2097 Build_Initialization_Call (Loc,
2098 Id_Ref => Ref,
2099 Typ => RTE (RC),
2100 In_Init_Proc => Within_Init_Proc));
2101 end if;
2103 Append_To (L,
2104 Make_Procedure_Call_Statement (Loc,
2105 Name =>
2106 New_Reference_To (
2107 Find_Prim_Op (RTE (RC), Name_Initialize), Loc),
2108 Parameter_Associations =>
2109 New_List (New_Copy_Tree (Ref))));
2111 Append_To (L,
2112 Make_Attach_Call (
2113 Obj_Ref => New_Copy_Tree (Ref),
2114 Flist_Ref => F,
2115 With_Attach => Attach));
2117 return L;
2118 end Init_Controller;
2120 -------------------------
2121 -- Is_Int_Range_Bounds --
2122 -------------------------
2124 function Is_Int_Range_Bounds (Bounds : Node_Id) return Boolean is
2125 begin
2126 return Nkind (Bounds) = N_Range
2127 and then Nkind (Low_Bound (Bounds)) = N_Integer_Literal
2128 and then Nkind (High_Bound (Bounds)) = N_Integer_Literal;
2129 end Is_Int_Range_Bounds;
2131 -------------------------------
2132 -- Gen_Ctrl_Actions_For_Aggr --
2133 -------------------------------
2135 procedure Gen_Ctrl_Actions_For_Aggr is
2136 Alloc : Node_Id := Empty;
2138 begin
2139 -- Do the work only the first time this is called
2141 if Ctrl_Stuff_Done then
2142 return;
2143 end if;
2145 Ctrl_Stuff_Done := True;
2147 if Present (Obj)
2148 and then Finalize_Storage_Only (Typ)
2149 and then
2150 (Is_Library_Level_Entity (Obj)
2151 or else Entity (Constant_Value (RTE (RE_Garbage_Collected))) =
2152 Standard_True)
2154 -- why not Is_True (Expr_Value (RTE (RE_Garbaage_Collected) ???
2155 then
2156 Attach := Make_Integer_Literal (Loc, 0);
2158 elsif Nkind (Parent (N)) = N_Qualified_Expression
2159 and then Nkind (Parent (Parent (N))) = N_Allocator
2160 then
2161 Alloc := Parent (Parent (N));
2162 Attach := Make_Integer_Literal (Loc, 2);
2164 else
2165 Attach := Make_Integer_Literal (Loc, 1);
2166 end if;
2168 -- Determine the external finalization list. It is either the
2169 -- finalization list of the outer-scope or the one coming from
2170 -- an outer aggregate. When the target is not a temporary, the
2171 -- proper scope is the scope of the target rather than the
2172 -- potentially transient current scope.
2174 if Needs_Finalization (Typ) then
2176 -- The current aggregate belongs to an allocator which creates
2177 -- an object through an anonymous access type or acts as the root
2178 -- of a coextension chain.
2180 if Present (Alloc)
2181 and then
2182 (Is_Coextension_Root (Alloc)
2183 or else Ekind (Etype (Alloc)) = E_Anonymous_Access_Type)
2184 then
2185 if No (Associated_Final_Chain (Etype (Alloc))) then
2186 Build_Final_List (Alloc, Etype (Alloc));
2187 end if;
2189 External_Final_List :=
2190 Make_Selected_Component (Loc,
2191 Prefix =>
2192 New_Reference_To (
2193 Associated_Final_Chain (Etype (Alloc)), Loc),
2194 Selector_Name =>
2195 Make_Identifier (Loc, Name_F));
2197 elsif Present (Flist) then
2198 External_Final_List := New_Copy_Tree (Flist);
2200 elsif Is_Entity_Name (Target)
2201 and then Present (Scope (Entity (Target)))
2202 then
2203 External_Final_List :=
2204 Find_Final_List (Scope (Entity (Target)));
2206 else
2207 External_Final_List := Find_Final_List (Current_Scope);
2208 end if;
2209 else
2210 External_Final_List := Empty;
2211 end if;
2213 -- Initialize and attach the outer object in the is_controlled case
2215 if Is_Controlled (Typ) then
2216 if Ancestor_Is_Subtype_Mark then
2217 Ref := Convert_To (Init_Typ, New_Copy_Tree (Target));
2218 Set_Assignment_OK (Ref);
2219 Append_To (L,
2220 Make_Procedure_Call_Statement (Loc,
2221 Name =>
2222 New_Reference_To
2223 (Find_Prim_Op (Init_Typ, Name_Initialize), Loc),
2224 Parameter_Associations => New_List (New_Copy_Tree (Ref))));
2225 end if;
2227 if not Has_Controlled_Component (Typ) then
2228 Ref := New_Copy_Tree (Target);
2229 Set_Assignment_OK (Ref);
2231 -- This is an aggregate of a coextension. Do not produce a
2232 -- finalization call, but rather attach the reference of the
2233 -- aggregate to its coextension chain.
2235 if Present (Alloc)
2236 and then Is_Dynamic_Coextension (Alloc)
2237 then
2238 if No (Coextensions (Alloc)) then
2239 Set_Coextensions (Alloc, New_Elmt_List);
2240 end if;
2242 Append_Elmt (Ref, Coextensions (Alloc));
2243 else
2244 Append_To (L,
2245 Make_Attach_Call (
2246 Obj_Ref => Ref,
2247 Flist_Ref => New_Copy_Tree (External_Final_List),
2248 With_Attach => Attach));
2249 end if;
2250 end if;
2251 end if;
2253 -- In the Has_Controlled component case, all the intermediate
2254 -- controllers must be initialized.
2256 if Has_Controlled_Component (Typ)
2257 and not Is_Limited_Ancestor_Expansion
2258 then
2259 declare
2260 Inner_Typ : Entity_Id;
2261 Outer_Typ : Entity_Id;
2262 At_Root : Boolean;
2264 begin
2265 -- Find outer type with a controller
2267 Outer_Typ := Base_Type (Typ);
2268 while Outer_Typ /= Init_Typ
2269 and then not Has_New_Controlled_Component (Outer_Typ)
2270 loop
2271 Outer_Typ := Etype (Outer_Typ);
2272 end loop;
2274 -- Attach it to the outer record controller to the external
2275 -- final list.
2277 if Outer_Typ = Init_Typ then
2278 Append_List_To (L,
2279 Init_Controller (
2280 Target => Target,
2281 Typ => Outer_Typ,
2282 F => External_Final_List,
2283 Attach => Attach,
2284 Init_Pr => False));
2286 At_Root := True;
2287 Inner_Typ := Init_Typ;
2289 else
2290 Append_List_To (L,
2291 Init_Controller (
2292 Target => Target,
2293 Typ => Outer_Typ,
2294 F => External_Final_List,
2295 Attach => Attach,
2296 Init_Pr => True));
2298 Inner_Typ := Etype (Outer_Typ);
2299 At_Root :=
2300 not Is_Tagged_Type (Typ) or else Inner_Typ = Outer_Typ;
2301 end if;
2303 -- The outer object has to be attached as well
2305 if Is_Controlled (Typ) then
2306 Ref := New_Copy_Tree (Target);
2307 Set_Assignment_OK (Ref);
2308 Append_To (L,
2309 Make_Attach_Call (
2310 Obj_Ref => Ref,
2311 Flist_Ref => New_Copy_Tree (External_Final_List),
2312 With_Attach => New_Copy_Tree (Attach)));
2313 end if;
2315 -- Initialize the internal controllers for tagged types with
2316 -- more than one controller.
2318 while not At_Root and then Inner_Typ /= Init_Typ loop
2319 if Has_New_Controlled_Component (Inner_Typ) then
2320 F :=
2321 Make_Selected_Component (Loc,
2322 Prefix =>
2323 Convert_To (Outer_Typ, New_Copy_Tree (Target)),
2324 Selector_Name =>
2325 Make_Identifier (Loc, Name_uController));
2326 F :=
2327 Make_Selected_Component (Loc,
2328 Prefix => F,
2329 Selector_Name => Make_Identifier (Loc, Name_F));
2331 Append_List_To (L,
2332 Init_Controller (
2333 Target => Target,
2334 Typ => Inner_Typ,
2335 F => F,
2336 Attach => Make_Integer_Literal (Loc, 1),
2337 Init_Pr => True));
2338 Outer_Typ := Inner_Typ;
2339 end if;
2341 -- Stop at the root
2343 At_Root := Inner_Typ = Etype (Inner_Typ);
2344 Inner_Typ := Etype (Inner_Typ);
2345 end loop;
2347 -- If not done yet attach the controller of the ancestor part
2349 if Outer_Typ /= Init_Typ
2350 and then Inner_Typ = Init_Typ
2351 and then Has_Controlled_Component (Init_Typ)
2352 then
2353 F :=
2354 Make_Selected_Component (Loc,
2355 Prefix => Convert_To (Outer_Typ, New_Copy_Tree (Target)),
2356 Selector_Name =>
2357 Make_Identifier (Loc, Name_uController));
2358 F :=
2359 Make_Selected_Component (Loc,
2360 Prefix => F,
2361 Selector_Name => Make_Identifier (Loc, Name_F));
2363 Attach := Make_Integer_Literal (Loc, 1);
2364 Append_List_To (L,
2365 Init_Controller (
2366 Target => Target,
2367 Typ => Init_Typ,
2368 F => F,
2369 Attach => Attach,
2370 Init_Pr => False));
2372 -- Note: Init_Pr is False because the ancestor part has
2373 -- already been initialized either way (by default, if
2374 -- given by a type name, otherwise from the expression).
2376 end if;
2377 end;
2378 end if;
2379 end Gen_Ctrl_Actions_For_Aggr;
2381 function Replace_Type (Expr : Node_Id) return Traverse_Result;
2382 -- If the aggregate contains a self-reference, traverse each expression
2383 -- to replace a possible self-reference with a reference to the proper
2384 -- component of the target of the assignment.
2386 ------------------
2387 -- Replace_Type --
2388 ------------------
2390 function Replace_Type (Expr : Node_Id) return Traverse_Result is
2391 begin
2392 -- Note regarding the Root_Type test below: Aggregate components for
2393 -- self-referential types include attribute references to the current
2394 -- instance, of the form: Typ'access, etc.. These references are
2395 -- rewritten as references to the target of the aggregate: the
2396 -- left-hand side of an assignment, the entity in a declaration,
2397 -- or a temporary. Without this test, we would improperly extended
2398 -- this rewriting to attribute references whose prefix was not the
2399 -- type of the aggregate.
2401 if Nkind (Expr) = N_Attribute_Reference
2402 and then Is_Entity_Name (Prefix (Expr))
2403 and then Is_Type (Entity (Prefix (Expr)))
2404 and then Root_Type (Etype (N)) = Root_Type (Entity (Prefix (Expr)))
2405 then
2406 if Is_Entity_Name (Lhs) then
2407 Rewrite (Prefix (Expr),
2408 New_Occurrence_Of (Entity (Lhs), Loc));
2410 elsif Nkind (Lhs) = N_Selected_Component then
2411 Rewrite (Expr,
2412 Make_Attribute_Reference (Loc,
2413 Attribute_Name => Name_Unrestricted_Access,
2414 Prefix => New_Copy_Tree (Prefix (Lhs))));
2415 Set_Analyzed (Parent (Expr), False);
2417 else
2418 Rewrite (Expr,
2419 Make_Attribute_Reference (Loc,
2420 Attribute_Name => Name_Unrestricted_Access,
2421 Prefix => New_Copy_Tree (Lhs)));
2422 Set_Analyzed (Parent (Expr), False);
2423 end if;
2424 end if;
2426 return OK;
2427 end Replace_Type;
2429 procedure Replace_Self_Reference is
2430 new Traverse_Proc (Replace_Type);
2432 -- Start of processing for Build_Record_Aggr_Code
2434 begin
2435 if Has_Self_Reference (N) then
2436 Replace_Self_Reference (N);
2437 end if;
2439 -- If the target of the aggregate is class-wide, we must convert it
2440 -- to the actual type of the aggregate, so that the proper components
2441 -- are visible. We know already that the types are compatible.
2443 if Present (Etype (Lhs))
2444 and then Is_Class_Wide_Type (Etype (Lhs))
2445 then
2446 Target := Unchecked_Convert_To (Typ, Lhs);
2447 else
2448 Target := Lhs;
2449 end if;
2451 -- Deal with the ancestor part of extension aggregates or with the
2452 -- discriminants of the root type.
2454 if Nkind (N) = N_Extension_Aggregate then
2455 declare
2456 A : constant Node_Id := Ancestor_Part (N);
2457 Assign : List_Id;
2459 begin
2460 -- If the ancestor part is a subtype mark "T", we generate
2462 -- init-proc (T(tmp)); if T is constrained and
2463 -- init-proc (S(tmp)); where S applies an appropriate
2464 -- constraint if T is unconstrained
2466 if Is_Entity_Name (A) and then Is_Type (Entity (A)) then
2467 Ancestor_Is_Subtype_Mark := True;
2469 if Is_Constrained (Entity (A)) then
2470 Init_Typ := Entity (A);
2472 -- For an ancestor part given by an unconstrained type mark,
2473 -- create a subtype constrained by appropriate corresponding
2474 -- discriminant values coming from either associations of the
2475 -- aggregate or a constraint on a parent type. The subtype will
2476 -- be used to generate the correct default value for the
2477 -- ancestor part.
2479 elsif Has_Discriminants (Entity (A)) then
2480 declare
2481 Anc_Typ : constant Entity_Id := Entity (A);
2482 Anc_Constr : constant List_Id := New_List;
2483 Discrim : Entity_Id;
2484 Disc_Value : Node_Id;
2485 New_Indic : Node_Id;
2486 Subt_Decl : Node_Id;
2488 begin
2489 Discrim := First_Discriminant (Anc_Typ);
2490 while Present (Discrim) loop
2491 Disc_Value := Ancestor_Discriminant_Value (Discrim);
2492 Append_To (Anc_Constr, Disc_Value);
2493 Next_Discriminant (Discrim);
2494 end loop;
2496 New_Indic :=
2497 Make_Subtype_Indication (Loc,
2498 Subtype_Mark => New_Occurrence_Of (Anc_Typ, Loc),
2499 Constraint =>
2500 Make_Index_Or_Discriminant_Constraint (Loc,
2501 Constraints => Anc_Constr));
2503 Init_Typ := Create_Itype (Ekind (Anc_Typ), N);
2505 Subt_Decl :=
2506 Make_Subtype_Declaration (Loc,
2507 Defining_Identifier => Init_Typ,
2508 Subtype_Indication => New_Indic);
2510 -- Itypes must be analyzed with checks off Declaration
2511 -- must have a parent for proper handling of subsidiary
2512 -- actions.
2514 Set_Parent (Subt_Decl, N);
2515 Analyze (Subt_Decl, Suppress => All_Checks);
2516 end;
2517 end if;
2519 Ref := Convert_To (Init_Typ, New_Copy_Tree (Target));
2520 Set_Assignment_OK (Ref);
2522 if Has_Default_Init_Comps (N)
2523 or else Has_Task (Base_Type (Init_Typ))
2524 then
2525 Append_List_To (L,
2526 Build_Initialization_Call (Loc,
2527 Id_Ref => Ref,
2528 Typ => Init_Typ,
2529 In_Init_Proc => Within_Init_Proc,
2530 With_Default_Init => True));
2531 else
2532 Append_List_To (L,
2533 Build_Initialization_Call (Loc,
2534 Id_Ref => Ref,
2535 Typ => Init_Typ,
2536 In_Init_Proc => Within_Init_Proc));
2537 end if;
2539 if Is_Constrained (Entity (A))
2540 and then Has_Discriminants (Entity (A))
2541 then
2542 Check_Ancestor_Discriminants (Entity (A));
2543 end if;
2545 -- Ada 2005 (AI-287): If the ancestor part is an aggregate of
2546 -- limited type, a recursive call expands the ancestor. Note that
2547 -- in the limited case, the ancestor part must be either a
2548 -- function call (possibly qualified, or wrapped in an unchecked
2549 -- conversion) or aggregate (definitely qualified).
2550 -- The ancestor part can also be a function call (that may be
2551 -- transformed into an explicit dereference) or a qualification
2552 -- of one such.
2554 elsif Is_Limited_Type (Etype (A))
2555 and then Nkind_In (Unqualify (A), N_Aggregate,
2556 N_Extension_Aggregate)
2557 then
2558 Ancestor_Is_Expression := True;
2560 -- Set up finalization data for enclosing record, because
2561 -- controlled subcomponents of the ancestor part will be
2562 -- attached to it.
2564 Gen_Ctrl_Actions_For_Aggr;
2566 Append_List_To (L,
2567 Build_Record_Aggr_Code (
2568 N => Unqualify (A),
2569 Typ => Etype (Unqualify (A)),
2570 Lhs => Target,
2571 Flist => Flist,
2572 Obj => Obj,
2573 Is_Limited_Ancestor_Expansion => True));
2575 -- If the ancestor part is an expression "E", we generate
2577 -- T(tmp) := E;
2579 -- In Ada 2005, this includes the case of a (possibly qualified)
2580 -- limited function call. The assignment will turn into a
2581 -- build-in-place function call (for further details, see
2582 -- Make_Build_In_Place_Call_In_Assignment).
2584 else
2585 Ancestor_Is_Expression := True;
2586 Init_Typ := Etype (A);
2588 -- If the ancestor part is an aggregate, force its full
2589 -- expansion, which was delayed.
2591 if Nkind_In (Unqualify (A), N_Aggregate,
2592 N_Extension_Aggregate)
2593 then
2594 Set_Analyzed (A, False);
2595 Set_Analyzed (Expression (A), False);
2596 end if;
2598 Ref := Convert_To (Init_Typ, New_Copy_Tree (Target));
2599 Set_Assignment_OK (Ref);
2601 -- Make the assignment without usual controlled actions since
2602 -- we only want the post adjust but not the pre finalize here
2603 -- Add manual adjust when necessary.
2605 Assign := New_List (
2606 Make_OK_Assignment_Statement (Loc,
2607 Name => Ref,
2608 Expression => A));
2609 Set_No_Ctrl_Actions (First (Assign));
2611 -- Assign the tag now to make sure that the dispatching call in
2612 -- the subsequent deep_adjust works properly (unless VM_Target,
2613 -- where tags are implicit).
2615 if VM_Target = No_VM then
2616 Instr :=
2617 Make_OK_Assignment_Statement (Loc,
2618 Name =>
2619 Make_Selected_Component (Loc,
2620 Prefix => New_Copy_Tree (Target),
2621 Selector_Name =>
2622 New_Reference_To
2623 (First_Tag_Component (Base_Type (Typ)), Loc)),
2625 Expression =>
2626 Unchecked_Convert_To (RTE (RE_Tag),
2627 New_Reference_To
2628 (Node (First_Elmt
2629 (Access_Disp_Table (Base_Type (Typ)))),
2630 Loc)));
2632 Set_Assignment_OK (Name (Instr));
2633 Append_To (Assign, Instr);
2635 -- Ada 2005 (AI-251): If tagged type has progenitors we must
2636 -- also initialize tags of the secondary dispatch tables.
2638 if Has_Interfaces (Base_Type (Typ)) then
2639 Init_Secondary_Tags
2640 (Typ => Base_Type (Typ),
2641 Target => Target,
2642 Stmts_List => Assign);
2643 end if;
2644 end if;
2646 -- Call Adjust manually
2648 if Needs_Finalization (Etype (A))
2649 and then not Is_Limited_Type (Etype (A))
2650 then
2651 Append_List_To (Assign,
2652 Make_Adjust_Call (
2653 Ref => New_Copy_Tree (Ref),
2654 Typ => Etype (A),
2655 Flist_Ref => New_Reference_To (
2656 RTE (RE_Global_Final_List), Loc),
2657 With_Attach => Make_Integer_Literal (Loc, 0)));
2658 end if;
2660 Append_To (L,
2661 Make_Unsuppress_Block (Loc, Name_Discriminant_Check, Assign));
2663 if Has_Discriminants (Init_Typ) then
2664 Check_Ancestor_Discriminants (Init_Typ);
2665 end if;
2666 end if;
2667 end;
2669 -- Normal case (not an extension aggregate)
2671 else
2672 -- Generate the discriminant expressions, component by component.
2673 -- If the base type is an unchecked union, the discriminants are
2674 -- unknown to the back-end and absent from a value of the type, so
2675 -- assignments for them are not emitted.
2677 if Has_Discriminants (Typ)
2678 and then not Is_Unchecked_Union (Base_Type (Typ))
2679 then
2680 -- If the type is derived, and constrains discriminants of the
2681 -- parent type, these discriminants are not components of the
2682 -- aggregate, and must be initialized explicitly. They are not
2683 -- visible components of the object, but can become visible with
2684 -- a view conversion to the ancestor.
2686 declare
2687 Btype : Entity_Id;
2688 Parent_Type : Entity_Id;
2689 Disc : Entity_Id;
2690 Discr_Val : Elmt_Id;
2692 begin
2693 Btype := Base_Type (Typ);
2694 while Is_Derived_Type (Btype)
2695 and then Present (Stored_Constraint (Btype))
2696 loop
2697 Parent_Type := Etype (Btype);
2699 Disc := First_Discriminant (Parent_Type);
2700 Discr_Val :=
2701 First_Elmt (Stored_Constraint (Base_Type (Typ)));
2702 while Present (Discr_Val) loop
2704 -- Only those discriminants of the parent that are not
2705 -- renamed by discriminants of the derived type need to
2706 -- be added explicitly.
2708 if not Is_Entity_Name (Node (Discr_Val))
2709 or else
2710 Ekind (Entity (Node (Discr_Val))) /= E_Discriminant
2711 then
2712 Comp_Expr :=
2713 Make_Selected_Component (Loc,
2714 Prefix => New_Copy_Tree (Target),
2715 Selector_Name => New_Occurrence_Of (Disc, Loc));
2717 Instr :=
2718 Make_OK_Assignment_Statement (Loc,
2719 Name => Comp_Expr,
2720 Expression => New_Copy_Tree (Node (Discr_Val)));
2722 Set_No_Ctrl_Actions (Instr);
2723 Append_To (L, Instr);
2724 end if;
2726 Next_Discriminant (Disc);
2727 Next_Elmt (Discr_Val);
2728 end loop;
2730 Btype := Base_Type (Parent_Type);
2731 end loop;
2732 end;
2734 -- Generate discriminant init values for the visible discriminants
2736 declare
2737 Discriminant : Entity_Id;
2738 Discriminant_Value : Node_Id;
2740 begin
2741 Discriminant := First_Stored_Discriminant (Typ);
2742 while Present (Discriminant) loop
2743 Comp_Expr :=
2744 Make_Selected_Component (Loc,
2745 Prefix => New_Copy_Tree (Target),
2746 Selector_Name => New_Occurrence_Of (Discriminant, Loc));
2748 Discriminant_Value :=
2749 Get_Discriminant_Value (
2750 Discriminant,
2751 N_Typ,
2752 Discriminant_Constraint (N_Typ));
2754 Instr :=
2755 Make_OK_Assignment_Statement (Loc,
2756 Name => Comp_Expr,
2757 Expression => New_Copy_Tree (Discriminant_Value));
2759 Set_No_Ctrl_Actions (Instr);
2760 Append_To (L, Instr);
2762 Next_Stored_Discriminant (Discriminant);
2763 end loop;
2764 end;
2765 end if;
2766 end if;
2768 -- Generate the assignments, component by component
2770 -- tmp.comp1 := Expr1_From_Aggr;
2771 -- tmp.comp2 := Expr2_From_Aggr;
2772 -- ....
2774 Comp := First (Component_Associations (N));
2775 while Present (Comp) loop
2776 Selector := Entity (First (Choices (Comp)));
2778 -- C++ constructors
2780 if Is_CPP_Constructor_Call (Expression (Comp)) then
2781 Append_List_To (L,
2782 Build_Initialization_Call (Loc,
2783 Id_Ref => Make_Selected_Component (Loc,
2784 Prefix => New_Copy_Tree (Target),
2785 Selector_Name => New_Occurrence_Of (Selector,
2786 Loc)),
2787 Typ => Etype (Selector),
2788 Enclos_Type => Typ,
2789 With_Default_Init => True,
2790 Constructor_Ref => Expression (Comp)));
2792 -- Ada 2005 (AI-287): For each default-initialized component generate
2793 -- a call to the corresponding IP subprogram if available.
2795 elsif Box_Present (Comp)
2796 and then Has_Non_Null_Base_Init_Proc (Etype (Selector))
2797 then
2798 if Ekind (Selector) /= E_Discriminant then
2799 Gen_Ctrl_Actions_For_Aggr;
2800 end if;
2802 -- Ada 2005 (AI-287): If the component type has tasks then
2803 -- generate the activation chain and master entities (except
2804 -- in case of an allocator because in that case these entities
2805 -- are generated by Build_Task_Allocate_Block_With_Init_Stmts).
2807 declare
2808 Ctype : constant Entity_Id := Etype (Selector);
2809 Inside_Allocator : Boolean := False;
2810 P : Node_Id := Parent (N);
2812 begin
2813 if Is_Task_Type (Ctype) or else Has_Task (Ctype) then
2814 while Present (P) loop
2815 if Nkind (P) = N_Allocator then
2816 Inside_Allocator := True;
2817 exit;
2818 end if;
2820 P := Parent (P);
2821 end loop;
2823 if not Inside_Init_Proc and not Inside_Allocator then
2824 Build_Activation_Chain_Entity (N);
2825 end if;
2826 end if;
2827 end;
2829 Append_List_To (L,
2830 Build_Initialization_Call (Loc,
2831 Id_Ref => Make_Selected_Component (Loc,
2832 Prefix => New_Copy_Tree (Target),
2833 Selector_Name => New_Occurrence_Of (Selector,
2834 Loc)),
2835 Typ => Etype (Selector),
2836 Enclos_Type => Typ,
2837 With_Default_Init => True));
2839 -- Prepare for component assignment
2841 elsif Ekind (Selector) /= E_Discriminant
2842 or else Nkind (N) = N_Extension_Aggregate
2843 then
2844 -- All the discriminants have now been assigned
2846 -- This is now a good moment to initialize and attach all the
2847 -- controllers. Their position may depend on the discriminants.
2849 if Ekind (Selector) /= E_Discriminant then
2850 Gen_Ctrl_Actions_For_Aggr;
2851 end if;
2853 Comp_Type := Etype (Selector);
2854 Comp_Expr :=
2855 Make_Selected_Component (Loc,
2856 Prefix => New_Copy_Tree (Target),
2857 Selector_Name => New_Occurrence_Of (Selector, Loc));
2859 if Nkind (Expression (Comp)) = N_Qualified_Expression then
2860 Expr_Q := Expression (Expression (Comp));
2861 else
2862 Expr_Q := Expression (Comp);
2863 end if;
2865 -- The controller is the one of the parent type defining the
2866 -- component (in case of inherited components).
2868 if Needs_Finalization (Comp_Type) then
2869 Internal_Final_List :=
2870 Make_Selected_Component (Loc,
2871 Prefix => Convert_To (
2872 Scope (Original_Record_Component (Selector)),
2873 New_Copy_Tree (Target)),
2874 Selector_Name =>
2875 Make_Identifier (Loc, Name_uController));
2877 Internal_Final_List :=
2878 Make_Selected_Component (Loc,
2879 Prefix => Internal_Final_List,
2880 Selector_Name => Make_Identifier (Loc, Name_F));
2882 -- The internal final list can be part of a constant object
2884 Set_Assignment_OK (Internal_Final_List);
2886 else
2887 Internal_Final_List := Empty;
2888 end if;
2890 -- Now either create the assignment or generate the code for the
2891 -- inner aggregate top-down.
2893 if Is_Delayed_Aggregate (Expr_Q) then
2895 -- We have the following case of aggregate nesting inside
2896 -- an object declaration:
2898 -- type Arr_Typ is array (Integer range <>) of ...;
2900 -- type Rec_Typ (...) is record
2901 -- Obj_Arr_Typ : Arr_Typ (A .. B);
2902 -- end record;
2904 -- Obj_Rec_Typ : Rec_Typ := (...,
2905 -- Obj_Arr_Typ => (X => (...), Y => (...)));
2907 -- The length of the ranges of the aggregate and Obj_Add_Typ
2908 -- are equal (B - A = Y - X), but they do not coincide (X /=
2909 -- A and B /= Y). This case requires array sliding which is
2910 -- performed in the following manner:
2912 -- subtype Arr_Sub is Arr_Typ (X .. Y);
2913 -- Temp : Arr_Sub;
2914 -- Temp (X) := (...);
2915 -- ...
2916 -- Temp (Y) := (...);
2917 -- Obj_Rec_Typ.Obj_Arr_Typ := Temp;
2919 if Ekind (Comp_Type) = E_Array_Subtype
2920 and then Is_Int_Range_Bounds (Aggregate_Bounds (Expr_Q))
2921 and then Is_Int_Range_Bounds (First_Index (Comp_Type))
2922 and then not
2923 Compatible_Int_Bounds
2924 (Agg_Bounds => Aggregate_Bounds (Expr_Q),
2925 Typ_Bounds => First_Index (Comp_Type))
2926 then
2927 -- Create the array subtype with bounds equal to those of
2928 -- the corresponding aggregate.
2930 declare
2931 SubE : constant Entity_Id :=
2932 Make_Defining_Identifier (Loc,
2933 New_Internal_Name ('T'));
2935 SubD : constant Node_Id :=
2936 Make_Subtype_Declaration (Loc,
2937 Defining_Identifier =>
2938 SubE,
2939 Subtype_Indication =>
2940 Make_Subtype_Indication (Loc,
2941 Subtype_Mark => New_Reference_To (
2942 Etype (Comp_Type), Loc),
2943 Constraint =>
2944 Make_Index_Or_Discriminant_Constraint (
2945 Loc, Constraints => New_List (
2946 New_Copy_Tree (Aggregate_Bounds (
2947 Expr_Q))))));
2949 -- Create a temporary array of the above subtype which
2950 -- will be used to capture the aggregate assignments.
2952 TmpE : constant Entity_Id :=
2953 Make_Defining_Identifier (Loc,
2954 New_Internal_Name ('A'));
2956 TmpD : constant Node_Id :=
2957 Make_Object_Declaration (Loc,
2958 Defining_Identifier =>
2959 TmpE,
2960 Object_Definition =>
2961 New_Reference_To (SubE, Loc));
2963 begin
2964 Set_No_Initialization (TmpD);
2965 Append_To (L, SubD);
2966 Append_To (L, TmpD);
2968 -- Expand aggregate into assignments to the temp array
2970 Append_List_To (L,
2971 Late_Expansion (Expr_Q, Comp_Type,
2972 New_Reference_To (TmpE, Loc), Internal_Final_List));
2974 -- Slide
2976 Append_To (L,
2977 Make_Assignment_Statement (Loc,
2978 Name => New_Copy_Tree (Comp_Expr),
2979 Expression => New_Reference_To (TmpE, Loc)));
2981 -- Do not pass the original aggregate to Gigi as is,
2982 -- since it will potentially clobber the front or the end
2983 -- of the array. Setting the expression to empty is safe
2984 -- since all aggregates are expanded into assignments.
2986 if Present (Obj) then
2987 Set_Expression (Parent (Obj), Empty);
2988 end if;
2989 end;
2991 -- Normal case (sliding not required)
2993 else
2994 Append_List_To (L,
2995 Late_Expansion (Expr_Q, Comp_Type, Comp_Expr,
2996 Internal_Final_List));
2997 end if;
2999 -- Expr_Q is not delayed aggregate
3001 else
3002 Instr :=
3003 Make_OK_Assignment_Statement (Loc,
3004 Name => Comp_Expr,
3005 Expression => Expression (Comp));
3007 Set_No_Ctrl_Actions (Instr);
3008 Append_To (L, Instr);
3010 -- Adjust the tag if tagged (because of possible view
3011 -- conversions), unless compiling for a VM where tags are
3012 -- implicit.
3014 -- tmp.comp._tag := comp_typ'tag;
3016 if Is_Tagged_Type (Comp_Type) and then VM_Target = No_VM then
3017 Instr :=
3018 Make_OK_Assignment_Statement (Loc,
3019 Name =>
3020 Make_Selected_Component (Loc,
3021 Prefix => New_Copy_Tree (Comp_Expr),
3022 Selector_Name =>
3023 New_Reference_To
3024 (First_Tag_Component (Comp_Type), Loc)),
3026 Expression =>
3027 Unchecked_Convert_To (RTE (RE_Tag),
3028 New_Reference_To
3029 (Node (First_Elmt (Access_Disp_Table (Comp_Type))),
3030 Loc)));
3032 Append_To (L, Instr);
3033 end if;
3035 -- Adjust and Attach the component to the proper controller
3037 -- Adjust (tmp.comp);
3038 -- Attach_To_Final_List (tmp.comp,
3039 -- comp_typ (tmp)._record_controller.f)
3041 if Needs_Finalization (Comp_Type)
3042 and then not Is_Limited_Type (Comp_Type)
3043 then
3044 Append_List_To (L,
3045 Make_Adjust_Call (
3046 Ref => New_Copy_Tree (Comp_Expr),
3047 Typ => Comp_Type,
3048 Flist_Ref => Internal_Final_List,
3049 With_Attach => Make_Integer_Literal (Loc, 1)));
3050 end if;
3051 end if;
3053 -- ???
3055 elsif Ekind (Selector) = E_Discriminant
3056 and then Nkind (N) /= N_Extension_Aggregate
3057 and then Nkind (Parent (N)) = N_Component_Association
3058 and then Is_Constrained (Typ)
3059 then
3060 -- We must check that the discriminant value imposed by the
3061 -- context is the same as the value given in the subaggregate,
3062 -- because after the expansion into assignments there is no
3063 -- record on which to perform a regular discriminant check.
3065 declare
3066 D_Val : Elmt_Id;
3067 Disc : Entity_Id;
3069 begin
3070 D_Val := First_Elmt (Discriminant_Constraint (Typ));
3071 Disc := First_Discriminant (Typ);
3072 while Chars (Disc) /= Chars (Selector) loop
3073 Next_Discriminant (Disc);
3074 Next_Elmt (D_Val);
3075 end loop;
3077 pragma Assert (Present (D_Val));
3079 -- This check cannot performed for components that are
3080 -- constrained by a current instance, because this is not a
3081 -- value that can be compared with the actual constraint.
3083 if Nkind (Node (D_Val)) /= N_Attribute_Reference
3084 or else not Is_Entity_Name (Prefix (Node (D_Val)))
3085 or else not Is_Type (Entity (Prefix (Node (D_Val))))
3086 then
3087 Append_To (L,
3088 Make_Raise_Constraint_Error (Loc,
3089 Condition =>
3090 Make_Op_Ne (Loc,
3091 Left_Opnd => New_Copy_Tree (Node (D_Val)),
3092 Right_Opnd => Expression (Comp)),
3093 Reason => CE_Discriminant_Check_Failed));
3095 else
3096 -- Find self-reference in previous discriminant assignment,
3097 -- and replace with proper expression.
3099 declare
3100 Ass : Node_Id;
3102 begin
3103 Ass := First (L);
3104 while Present (Ass) loop
3105 if Nkind (Ass) = N_Assignment_Statement
3106 and then Nkind (Name (Ass)) = N_Selected_Component
3107 and then Chars (Selector_Name (Name (Ass))) =
3108 Chars (Disc)
3109 then
3110 Set_Expression
3111 (Ass, New_Copy_Tree (Expression (Comp)));
3112 exit;
3113 end if;
3114 Next (Ass);
3115 end loop;
3116 end;
3117 end if;
3118 end;
3119 end if;
3121 Next (Comp);
3122 end loop;
3124 -- If the type is tagged, the tag needs to be initialized (unless
3125 -- compiling for the Java VM where tags are implicit). It is done
3126 -- late in the initialization process because in some cases, we call
3127 -- the init proc of an ancestor which will not leave out the right tag
3129 if Ancestor_Is_Expression then
3130 null;
3132 elsif Is_Tagged_Type (Typ) and then VM_Target = No_VM then
3133 Instr :=
3134 Make_OK_Assignment_Statement (Loc,
3135 Name =>
3136 Make_Selected_Component (Loc,
3137 Prefix => New_Copy_Tree (Target),
3138 Selector_Name =>
3139 New_Reference_To
3140 (First_Tag_Component (Base_Type (Typ)), Loc)),
3142 Expression =>
3143 Unchecked_Convert_To (RTE (RE_Tag),
3144 New_Reference_To
3145 (Node (First_Elmt (Access_Disp_Table (Base_Type (Typ)))),
3146 Loc)));
3148 Append_To (L, Instr);
3150 -- Ada 2005 (AI-251): If the tagged type has been derived from
3151 -- abstract interfaces we must also initialize the tags of the
3152 -- secondary dispatch tables.
3154 if Has_Interfaces (Base_Type (Typ)) then
3155 Init_Secondary_Tags
3156 (Typ => Base_Type (Typ),
3157 Target => Target,
3158 Stmts_List => L);
3159 end if;
3160 end if;
3162 -- If the controllers have not been initialized yet (by lack of non-
3163 -- discriminant components), let's do it now.
3165 Gen_Ctrl_Actions_For_Aggr;
3167 return L;
3168 end Build_Record_Aggr_Code;
3170 -------------------------------
3171 -- Convert_Aggr_In_Allocator --
3172 -------------------------------
3174 procedure Convert_Aggr_In_Allocator
3175 (Alloc : Node_Id;
3176 Decl : Node_Id;
3177 Aggr : Node_Id)
3179 Loc : constant Source_Ptr := Sloc (Aggr);
3180 Typ : constant Entity_Id := Etype (Aggr);
3181 Temp : constant Entity_Id := Defining_Identifier (Decl);
3183 Occ : constant Node_Id :=
3184 Unchecked_Convert_To (Typ,
3185 Make_Explicit_Dereference (Loc,
3186 New_Reference_To (Temp, Loc)));
3188 Access_Type : constant Entity_Id := Etype (Temp);
3189 Flist : Entity_Id;
3191 begin
3192 -- If the allocator is for an access discriminant, there is no
3193 -- finalization list for the anonymous access type, and the eventual
3194 -- finalization of the object is handled through the coextension
3195 -- mechanism. If the enclosing object is not dynamically allocated,
3196 -- the access discriminant is itself placed on the stack. Otherwise,
3197 -- some other finalization list is used (see exp_ch4.adb).
3199 -- Decl has been inserted in the code ahead of the allocator, using
3200 -- Insert_Actions. We use Insert_Actions below as well, to ensure that
3201 -- subsequent insertions are done in the proper order. Using (for
3202 -- example) Insert_Actions_After to place the expanded aggregate
3203 -- immediately after Decl may lead to out-of-order references if the
3204 -- allocator has generated a finalization list, as when the designated
3205 -- object is controlled and there is an open transient scope.
3207 if Ekind (Access_Type) = E_Anonymous_Access_Type
3208 and then Nkind (Associated_Node_For_Itype (Access_Type)) =
3209 N_Discriminant_Specification
3210 then
3211 Flist := Empty;
3212 else
3213 Flist := Find_Final_List (Access_Type);
3214 end if;
3216 if Is_Array_Type (Typ) then
3217 Convert_Array_Aggr_In_Allocator (Decl, Aggr, Occ);
3219 elsif Has_Default_Init_Comps (Aggr) then
3220 declare
3221 L : constant List_Id := New_List;
3222 Init_Stmts : List_Id;
3224 begin
3225 Init_Stmts :=
3226 Late_Expansion
3227 (Aggr, Typ, Occ,
3228 Flist,
3229 Associated_Final_Chain (Base_Type (Access_Type)));
3231 -- ??? Dubious actual for Obj: expect 'the original object being
3232 -- initialized'
3234 if Has_Task (Typ) then
3235 Build_Task_Allocate_Block_With_Init_Stmts (L, Aggr, Init_Stmts);
3236 Insert_Actions (Alloc, L);
3237 else
3238 Insert_Actions (Alloc, Init_Stmts);
3239 end if;
3240 end;
3242 else
3243 Insert_Actions (Alloc,
3244 Late_Expansion
3245 (Aggr, Typ, Occ, Flist,
3246 Associated_Final_Chain (Base_Type (Access_Type))));
3248 -- ??? Dubious actual for Obj: expect 'the original object being
3249 -- initialized'
3251 end if;
3252 end Convert_Aggr_In_Allocator;
3254 --------------------------------
3255 -- Convert_Aggr_In_Assignment --
3256 --------------------------------
3258 procedure Convert_Aggr_In_Assignment (N : Node_Id) is
3259 Aggr : Node_Id := Expression (N);
3260 Typ : constant Entity_Id := Etype (Aggr);
3261 Occ : constant Node_Id := New_Copy_Tree (Name (N));
3263 begin
3264 if Nkind (Aggr) = N_Qualified_Expression then
3265 Aggr := Expression (Aggr);
3266 end if;
3268 Insert_Actions_After (N,
3269 Late_Expansion
3270 (Aggr, Typ, Occ,
3271 Find_Final_List (Typ, New_Copy_Tree (Occ))));
3272 end Convert_Aggr_In_Assignment;
3274 ---------------------------------
3275 -- Convert_Aggr_In_Object_Decl --
3276 ---------------------------------
3278 procedure Convert_Aggr_In_Object_Decl (N : Node_Id) is
3279 Obj : constant Entity_Id := Defining_Identifier (N);
3280 Aggr : Node_Id := Expression (N);
3281 Loc : constant Source_Ptr := Sloc (Aggr);
3282 Typ : constant Entity_Id := Etype (Aggr);
3283 Occ : constant Node_Id := New_Occurrence_Of (Obj, Loc);
3285 function Discriminants_Ok return Boolean;
3286 -- If the object type is constrained, the discriminants in the
3287 -- aggregate must be checked against the discriminants of the subtype.
3288 -- This cannot be done using Apply_Discriminant_Checks because after
3289 -- expansion there is no aggregate left to check.
3291 ----------------------
3292 -- Discriminants_Ok --
3293 ----------------------
3295 function Discriminants_Ok return Boolean is
3296 Cond : Node_Id := Empty;
3297 Check : Node_Id;
3298 D : Entity_Id;
3299 Disc1 : Elmt_Id;
3300 Disc2 : Elmt_Id;
3301 Val1 : Node_Id;
3302 Val2 : Node_Id;
3304 begin
3305 D := First_Discriminant (Typ);
3306 Disc1 := First_Elmt (Discriminant_Constraint (Typ));
3307 Disc2 := First_Elmt (Discriminant_Constraint (Etype (Obj)));
3308 while Present (Disc1) and then Present (Disc2) loop
3309 Val1 := Node (Disc1);
3310 Val2 := Node (Disc2);
3312 if not Is_OK_Static_Expression (Val1)
3313 or else not Is_OK_Static_Expression (Val2)
3314 then
3315 Check := Make_Op_Ne (Loc,
3316 Left_Opnd => Duplicate_Subexpr (Val1),
3317 Right_Opnd => Duplicate_Subexpr (Val2));
3319 if No (Cond) then
3320 Cond := Check;
3322 else
3323 Cond := Make_Or_Else (Loc,
3324 Left_Opnd => Cond,
3325 Right_Opnd => Check);
3326 end if;
3328 elsif Expr_Value (Val1) /= Expr_Value (Val2) then
3329 Apply_Compile_Time_Constraint_Error (Aggr,
3330 Msg => "incorrect value for discriminant&?",
3331 Reason => CE_Discriminant_Check_Failed,
3332 Ent => D);
3333 return False;
3334 end if;
3336 Next_Discriminant (D);
3337 Next_Elmt (Disc1);
3338 Next_Elmt (Disc2);
3339 end loop;
3341 -- If any discriminant constraint is non-static, emit a check
3343 if Present (Cond) then
3344 Insert_Action (N,
3345 Make_Raise_Constraint_Error (Loc,
3346 Condition => Cond,
3347 Reason => CE_Discriminant_Check_Failed));
3348 end if;
3350 return True;
3351 end Discriminants_Ok;
3353 -- Start of processing for Convert_Aggr_In_Object_Decl
3355 begin
3356 Set_Assignment_OK (Occ);
3358 if Nkind (Aggr) = N_Qualified_Expression then
3359 Aggr := Expression (Aggr);
3360 end if;
3362 if Has_Discriminants (Typ)
3363 and then Typ /= Etype (Obj)
3364 and then Is_Constrained (Etype (Obj))
3365 and then not Discriminants_Ok
3366 then
3367 return;
3368 end if;
3370 -- If the context is an extended return statement, it has its own
3371 -- finalization machinery (i.e. works like a transient scope) and
3372 -- we do not want to create an additional one, because objects on
3373 -- the finalization list of the return must be moved to the caller's
3374 -- finalization list to complete the return.
3376 -- However, if the aggregate is limited, it is built in place, and the
3377 -- controlled components are not assigned to intermediate temporaries
3378 -- so there is no need for a transient scope in this case either.
3380 if Requires_Transient_Scope (Typ)
3381 and then Ekind (Current_Scope) /= E_Return_Statement
3382 and then not Is_Limited_Type (Typ)
3383 then
3384 Establish_Transient_Scope
3385 (Aggr,
3386 Sec_Stack =>
3387 Is_Controlled (Typ) or else Has_Controlled_Component (Typ));
3388 end if;
3390 Insert_Actions_After (N, Late_Expansion (Aggr, Typ, Occ, Obj => Obj));
3391 Set_No_Initialization (N);
3392 Initialize_Discriminants (N, Typ);
3393 end Convert_Aggr_In_Object_Decl;
3395 -------------------------------------
3396 -- Convert_Array_Aggr_In_Allocator --
3397 -------------------------------------
3399 procedure Convert_Array_Aggr_In_Allocator
3400 (Decl : Node_Id;
3401 Aggr : Node_Id;
3402 Target : Node_Id)
3404 Aggr_Code : List_Id;
3405 Typ : constant Entity_Id := Etype (Aggr);
3406 Ctyp : constant Entity_Id := Component_Type (Typ);
3408 begin
3409 -- The target is an explicit dereference of the allocated object.
3410 -- Generate component assignments to it, as for an aggregate that
3411 -- appears on the right-hand side of an assignment statement.
3413 Aggr_Code :=
3414 Build_Array_Aggr_Code (Aggr,
3415 Ctype => Ctyp,
3416 Index => First_Index (Typ),
3417 Into => Target,
3418 Scalar_Comp => Is_Scalar_Type (Ctyp));
3420 Insert_Actions_After (Decl, Aggr_Code);
3421 end Convert_Array_Aggr_In_Allocator;
3423 ----------------------------
3424 -- Convert_To_Assignments --
3425 ----------------------------
3427 procedure Convert_To_Assignments (N : Node_Id; Typ : Entity_Id) is
3428 Loc : constant Source_Ptr := Sloc (N);
3429 T : Entity_Id;
3430 Temp : Entity_Id;
3432 Instr : Node_Id;
3433 Target_Expr : Node_Id;
3434 Parent_Kind : Node_Kind;
3435 Unc_Decl : Boolean := False;
3436 Parent_Node : Node_Id;
3438 begin
3439 pragma Assert (not Is_Static_Dispatch_Table_Aggregate (N));
3440 pragma Assert (Is_Record_Type (Typ));
3442 Parent_Node := Parent (N);
3443 Parent_Kind := Nkind (Parent_Node);
3445 if Parent_Kind = N_Qualified_Expression then
3447 -- Check if we are in a unconstrained declaration because in this
3448 -- case the current delayed expansion mechanism doesn't work when
3449 -- the declared object size depend on the initializing expr.
3451 begin
3452 Parent_Node := Parent (Parent_Node);
3453 Parent_Kind := Nkind (Parent_Node);
3455 if Parent_Kind = N_Object_Declaration then
3456 Unc_Decl :=
3457 not Is_Entity_Name (Object_Definition (Parent_Node))
3458 or else Has_Discriminants
3459 (Entity (Object_Definition (Parent_Node)))
3460 or else Is_Class_Wide_Type
3461 (Entity (Object_Definition (Parent_Node)));
3462 end if;
3463 end;
3464 end if;
3466 -- Just set the Delay flag in the cases where the transformation will be
3467 -- done top down from above.
3469 if False
3471 -- Internal aggregate (transformed when expanding the parent)
3473 or else Parent_Kind = N_Aggregate
3474 or else Parent_Kind = N_Extension_Aggregate
3475 or else Parent_Kind = N_Component_Association
3477 -- Allocator (see Convert_Aggr_In_Allocator)
3479 or else Parent_Kind = N_Allocator
3481 -- Object declaration (see Convert_Aggr_In_Object_Decl)
3483 or else (Parent_Kind = N_Object_Declaration and then not Unc_Decl)
3485 -- Safe assignment (see Convert_Aggr_Assignments). So far only the
3486 -- assignments in init procs are taken into account.
3488 or else (Parent_Kind = N_Assignment_Statement
3489 and then Inside_Init_Proc)
3491 -- (Ada 2005) An inherently limited type in a return statement,
3492 -- which will be handled in a build-in-place fashion, and may be
3493 -- rewritten as an extended return and have its own finalization
3494 -- machinery. In the case of a simple return, the aggregate needs
3495 -- to be delayed until the scope for the return statement has been
3496 -- created, so that any finalization chain will be associated with
3497 -- that scope. For extended returns, we delay expansion to avoid the
3498 -- creation of an unwanted transient scope that could result in
3499 -- premature finalization of the return object (which is built in
3500 -- in place within the caller's scope).
3502 or else
3503 (Is_Inherently_Limited_Type (Typ)
3504 and then
3505 (Nkind (Parent (Parent_Node)) = N_Extended_Return_Statement
3506 or else Nkind (Parent_Node) = N_Simple_Return_Statement))
3507 then
3508 Set_Expansion_Delayed (N);
3509 return;
3510 end if;
3512 if Requires_Transient_Scope (Typ) then
3513 Establish_Transient_Scope
3514 (N, Sec_Stack =>
3515 Is_Controlled (Typ) or else Has_Controlled_Component (Typ));
3516 end if;
3518 -- If the aggregate is non-limited, create a temporary. If it is limited
3519 -- and the context is an assignment, this is a subaggregate for an
3520 -- enclosing aggregate being expanded. It must be built in place, so use
3521 -- the target of the current assignment.
3523 if Is_Limited_Type (Typ)
3524 and then Nkind (Parent (N)) = N_Assignment_Statement
3525 then
3526 Target_Expr := New_Copy_Tree (Name (Parent (N)));
3527 Insert_Actions
3528 (Parent (N), Build_Record_Aggr_Code (N, Typ, Target_Expr));
3529 Rewrite (Parent (N), Make_Null_Statement (Loc));
3531 else
3532 Temp := Make_Defining_Identifier (Loc, New_Internal_Name ('A'));
3534 -- If the type inherits unknown discriminants, use the view with
3535 -- known discriminants if available.
3537 if Has_Unknown_Discriminants (Typ)
3538 and then Present (Underlying_Record_View (Typ))
3539 then
3540 T := Underlying_Record_View (Typ);
3541 else
3542 T := Typ;
3543 end if;
3545 Instr :=
3546 Make_Object_Declaration (Loc,
3547 Defining_Identifier => Temp,
3548 Object_Definition => New_Occurrence_Of (T, Loc));
3550 Set_No_Initialization (Instr);
3551 Insert_Action (N, Instr);
3552 Initialize_Discriminants (Instr, T);
3553 Target_Expr := New_Occurrence_Of (Temp, Loc);
3554 Insert_Actions (N, Build_Record_Aggr_Code (N, T, Target_Expr));
3555 Rewrite (N, New_Occurrence_Of (Temp, Loc));
3556 Analyze_And_Resolve (N, T);
3557 end if;
3558 end Convert_To_Assignments;
3560 ---------------------------
3561 -- Convert_To_Positional --
3562 ---------------------------
3564 procedure Convert_To_Positional
3565 (N : Node_Id;
3566 Max_Others_Replicate : Nat := 5;
3567 Handle_Bit_Packed : Boolean := False)
3569 Typ : constant Entity_Id := Etype (N);
3571 Static_Components : Boolean := True;
3573 procedure Check_Static_Components;
3574 -- Check whether all components of the aggregate are compile-time known
3575 -- values, and can be passed as is to the back-end without further
3576 -- expansion.
3578 function Flatten
3579 (N : Node_Id;
3580 Ix : Node_Id;
3581 Ixb : Node_Id) return Boolean;
3582 -- Convert the aggregate into a purely positional form if possible. On
3583 -- entry the bounds of all dimensions are known to be static, and the
3584 -- total number of components is safe enough to expand.
3586 function Is_Flat (N : Node_Id; Dims : Int) return Boolean;
3587 -- Return True iff the array N is flat (which is not rivial in the case
3588 -- of multidimensionsl aggregates).
3590 -----------------------------
3591 -- Check_Static_Components --
3592 -----------------------------
3594 procedure Check_Static_Components is
3595 Expr : Node_Id;
3597 begin
3598 Static_Components := True;
3600 if Nkind (N) = N_String_Literal then
3601 null;
3603 elsif Present (Expressions (N)) then
3604 Expr := First (Expressions (N));
3605 while Present (Expr) loop
3606 if Nkind (Expr) /= N_Aggregate
3607 or else not Compile_Time_Known_Aggregate (Expr)
3608 or else Expansion_Delayed (Expr)
3609 then
3610 Static_Components := False;
3611 exit;
3612 end if;
3614 Next (Expr);
3615 end loop;
3616 end if;
3618 if Nkind (N) = N_Aggregate
3619 and then Present (Component_Associations (N))
3620 then
3621 Expr := First (Component_Associations (N));
3622 while Present (Expr) loop
3623 if Nkind (Expression (Expr)) = N_Integer_Literal then
3624 null;
3626 elsif Nkind (Expression (Expr)) /= N_Aggregate
3627 or else
3628 not Compile_Time_Known_Aggregate (Expression (Expr))
3629 or else Expansion_Delayed (Expression (Expr))
3630 then
3631 Static_Components := False;
3632 exit;
3633 end if;
3635 Next (Expr);
3636 end loop;
3637 end if;
3638 end Check_Static_Components;
3640 -------------
3641 -- Flatten --
3642 -------------
3644 function Flatten
3645 (N : Node_Id;
3646 Ix : Node_Id;
3647 Ixb : Node_Id) return Boolean
3649 Loc : constant Source_Ptr := Sloc (N);
3650 Blo : constant Node_Id := Type_Low_Bound (Etype (Ixb));
3651 Lo : constant Node_Id := Type_Low_Bound (Etype (Ix));
3652 Hi : constant Node_Id := Type_High_Bound (Etype (Ix));
3653 Lov : Uint;
3654 Hiv : Uint;
3656 begin
3657 if Nkind (Original_Node (N)) = N_String_Literal then
3658 return True;
3659 end if;
3661 if not Compile_Time_Known_Value (Lo)
3662 or else not Compile_Time_Known_Value (Hi)
3663 then
3664 return False;
3665 end if;
3667 Lov := Expr_Value (Lo);
3668 Hiv := Expr_Value (Hi);
3670 if Hiv < Lov
3671 or else not Compile_Time_Known_Value (Blo)
3672 then
3673 return False;
3674 end if;
3676 -- Determine if set of alternatives is suitable for conversion and
3677 -- build an array containing the values in sequence.
3679 declare
3680 Vals : array (UI_To_Int (Lov) .. UI_To_Int (Hiv))
3681 of Node_Id := (others => Empty);
3682 -- The values in the aggregate sorted appropriately
3684 Vlist : List_Id;
3685 -- Same data as Vals in list form
3687 Rep_Count : Nat;
3688 -- Used to validate Max_Others_Replicate limit
3690 Elmt : Node_Id;
3691 Num : Int := UI_To_Int (Lov);
3692 Choice : Node_Id;
3693 Lo, Hi : Node_Id;
3695 begin
3696 if Present (Expressions (N)) then
3697 Elmt := First (Expressions (N));
3698 while Present (Elmt) loop
3699 if Nkind (Elmt) = N_Aggregate
3700 and then Present (Next_Index (Ix))
3701 and then
3702 not Flatten (Elmt, Next_Index (Ix), Next_Index (Ixb))
3703 then
3704 return False;
3705 end if;
3707 Vals (Num) := Relocate_Node (Elmt);
3708 Num := Num + 1;
3710 Next (Elmt);
3711 end loop;
3712 end if;
3714 if No (Component_Associations (N)) then
3715 return True;
3716 end if;
3718 Elmt := First (Component_Associations (N));
3720 if Nkind (Expression (Elmt)) = N_Aggregate then
3721 if Present (Next_Index (Ix))
3722 and then
3723 not Flatten
3724 (Expression (Elmt), Next_Index (Ix), Next_Index (Ixb))
3725 then
3726 return False;
3727 end if;
3728 end if;
3730 Component_Loop : while Present (Elmt) loop
3731 Choice := First (Choices (Elmt));
3732 Choice_Loop : while Present (Choice) loop
3734 -- If we have an others choice, fill in the missing elements
3735 -- subject to the limit established by Max_Others_Replicate.
3737 if Nkind (Choice) = N_Others_Choice then
3738 Rep_Count := 0;
3740 for J in Vals'Range loop
3741 if No (Vals (J)) then
3742 Vals (J) := New_Copy_Tree (Expression (Elmt));
3743 Rep_Count := Rep_Count + 1;
3745 -- Check for maximum others replication. Note that
3746 -- we skip this test if either of the restrictions
3747 -- No_Elaboration_Code or No_Implicit_Loops is
3748 -- active, if this is a preelaborable unit or a
3749 -- predefined unit. This ensures that predefined
3750 -- units get the same level of constant folding in
3751 -- Ada 95 and Ada 05, where their categorization
3752 -- has changed.
3754 declare
3755 P : constant Entity_Id :=
3756 Cunit_Entity (Current_Sem_Unit);
3758 begin
3759 -- Check if duplication OK and if so continue
3760 -- processing.
3762 if Restriction_Active (No_Elaboration_Code)
3763 or else Restriction_Active (No_Implicit_Loops)
3764 or else Is_Preelaborated (P)
3765 or else (Ekind (P) = E_Package_Body
3766 and then
3767 Is_Preelaborated (Spec_Entity (P)))
3768 or else
3769 Is_Predefined_File_Name
3770 (Unit_File_Name (Get_Source_Unit (P)))
3771 then
3772 null;
3774 -- If duplication not OK, then we return False
3775 -- if the replication count is too high
3777 elsif Rep_Count > Max_Others_Replicate then
3778 return False;
3780 -- Continue on if duplication not OK, but the
3781 -- replication count is not excessive.
3783 else
3784 null;
3785 end if;
3786 end;
3787 end if;
3788 end loop;
3790 exit Component_Loop;
3792 -- Case of a subtype mark
3794 elsif Nkind (Choice) = N_Identifier
3795 and then Is_Type (Entity (Choice))
3796 then
3797 Lo := Type_Low_Bound (Etype (Choice));
3798 Hi := Type_High_Bound (Etype (Choice));
3800 -- Case of subtype indication
3802 elsif Nkind (Choice) = N_Subtype_Indication then
3803 Lo := Low_Bound (Range_Expression (Constraint (Choice)));
3804 Hi := High_Bound (Range_Expression (Constraint (Choice)));
3806 -- Case of a range
3808 elsif Nkind (Choice) = N_Range then
3809 Lo := Low_Bound (Choice);
3810 Hi := High_Bound (Choice);
3812 -- Normal subexpression case
3814 else pragma Assert (Nkind (Choice) in N_Subexpr);
3815 if not Compile_Time_Known_Value (Choice) then
3816 return False;
3818 else
3819 Vals (UI_To_Int (Expr_Value (Choice))) :=
3820 New_Copy_Tree (Expression (Elmt));
3821 goto Continue;
3822 end if;
3823 end if;
3825 -- Range cases merge with Lo,Hi said
3827 if not Compile_Time_Known_Value (Lo)
3828 or else
3829 not Compile_Time_Known_Value (Hi)
3830 then
3831 return False;
3832 else
3833 for J in UI_To_Int (Expr_Value (Lo)) ..
3834 UI_To_Int (Expr_Value (Hi))
3835 loop
3836 Vals (J) := New_Copy_Tree (Expression (Elmt));
3837 end loop;
3838 end if;
3840 <<Continue>>
3841 Next (Choice);
3842 end loop Choice_Loop;
3844 Next (Elmt);
3845 end loop Component_Loop;
3847 -- If we get here the conversion is possible
3849 Vlist := New_List;
3850 for J in Vals'Range loop
3851 Append (Vals (J), Vlist);
3852 end loop;
3854 Rewrite (N, Make_Aggregate (Loc, Expressions => Vlist));
3855 Set_Aggregate_Bounds (N, Aggregate_Bounds (Original_Node (N)));
3856 return True;
3857 end;
3858 end Flatten;
3860 -------------
3861 -- Is_Flat --
3862 -------------
3864 function Is_Flat (N : Node_Id; Dims : Int) return Boolean is
3865 Elmt : Node_Id;
3867 begin
3868 if Dims = 0 then
3869 return True;
3871 elsif Nkind (N) = N_Aggregate then
3872 if Present (Component_Associations (N)) then
3873 return False;
3875 else
3876 Elmt := First (Expressions (N));
3877 while Present (Elmt) loop
3878 if not Is_Flat (Elmt, Dims - 1) then
3879 return False;
3880 end if;
3882 Next (Elmt);
3883 end loop;
3885 return True;
3886 end if;
3887 else
3888 return True;
3889 end if;
3890 end Is_Flat;
3892 -- Start of processing for Convert_To_Positional
3894 begin
3895 -- Ada 2005 (AI-287): Do not convert in case of default initialized
3896 -- components because in this case will need to call the corresponding
3897 -- IP procedure.
3899 if Has_Default_Init_Comps (N) then
3900 return;
3901 end if;
3903 if Is_Flat (N, Number_Dimensions (Typ)) then
3904 return;
3905 end if;
3907 if Is_Bit_Packed_Array (Typ)
3908 and then not Handle_Bit_Packed
3909 then
3910 return;
3911 end if;
3913 -- Do not convert to positional if controlled components are involved
3914 -- since these require special processing
3916 if Has_Controlled_Component (Typ) then
3917 return;
3918 end if;
3920 Check_Static_Components;
3922 -- If the size is known, or all the components are static, try to
3923 -- build a fully positional aggregate.
3925 -- The size of the type may not be known for an aggregate with
3926 -- discriminated array components, but if the components are static
3927 -- it is still possible to verify statically that the length is
3928 -- compatible with the upper bound of the type, and therefore it is
3929 -- worth flattening such aggregates as well.
3931 -- For now the back-end expands these aggregates into individual
3932 -- assignments to the target anyway, but it is conceivable that
3933 -- it will eventually be able to treat such aggregates statically???
3935 if Aggr_Size_OK (N, Typ)
3936 and then Flatten (N, First_Index (Typ), First_Index (Base_Type (Typ)))
3937 then
3938 if Static_Components then
3939 Set_Compile_Time_Known_Aggregate (N);
3940 Set_Expansion_Delayed (N, False);
3941 end if;
3943 Analyze_And_Resolve (N, Typ);
3944 end if;
3945 end Convert_To_Positional;
3947 ----------------------------
3948 -- Expand_Array_Aggregate --
3949 ----------------------------
3951 -- Array aggregate expansion proceeds as follows:
3953 -- 1. If requested we generate code to perform all the array aggregate
3954 -- bound checks, specifically
3956 -- (a) Check that the index range defined by aggregate bounds is
3957 -- compatible with corresponding index subtype.
3959 -- (b) If an others choice is present check that no aggregate
3960 -- index is outside the bounds of the index constraint.
3962 -- (c) For multidimensional arrays make sure that all subaggregates
3963 -- corresponding to the same dimension have the same bounds.
3965 -- 2. Check for packed array aggregate which can be converted to a
3966 -- constant so that the aggregate disappeares completely.
3968 -- 3. Check case of nested aggregate. Generally nested aggregates are
3969 -- handled during the processing of the parent aggregate.
3971 -- 4. Check if the aggregate can be statically processed. If this is the
3972 -- case pass it as is to Gigi. Note that a necessary condition for
3973 -- static processing is that the aggregate be fully positional.
3975 -- 5. If in place aggregate expansion is possible (i.e. no need to create
3976 -- a temporary) then mark the aggregate as such and return. Otherwise
3977 -- create a new temporary and generate the appropriate initialization
3978 -- code.
3980 procedure Expand_Array_Aggregate (N : Node_Id) is
3981 Loc : constant Source_Ptr := Sloc (N);
3983 Typ : constant Entity_Id := Etype (N);
3984 Ctyp : constant Entity_Id := Component_Type (Typ);
3985 -- Typ is the correct constrained array subtype of the aggregate
3986 -- Ctyp is the corresponding component type.
3988 Aggr_Dimension : constant Pos := Number_Dimensions (Typ);
3989 -- Number of aggregate index dimensions
3991 Aggr_Low : array (1 .. Aggr_Dimension) of Node_Id;
3992 Aggr_High : array (1 .. Aggr_Dimension) of Node_Id;
3993 -- Low and High bounds of the constraint for each aggregate index
3995 Aggr_Index_Typ : array (1 .. Aggr_Dimension) of Entity_Id;
3996 -- The type of each index
3998 Maybe_In_Place_OK : Boolean;
3999 -- If the type is neither controlled nor packed and the aggregate
4000 -- is the expression in an assignment, assignment in place may be
4001 -- possible, provided other conditions are met on the LHS.
4003 Others_Present : array (1 .. Aggr_Dimension) of Boolean :=
4004 (others => False);
4005 -- If Others_Present (J) is True, then there is an others choice
4006 -- in one of the sub-aggregates of N at dimension J.
4008 procedure Build_Constrained_Type (Positional : Boolean);
4009 -- If the subtype is not static or unconstrained, build a constrained
4010 -- type using the computable sizes of the aggregate and its sub-
4011 -- aggregates.
4013 procedure Check_Bounds (Aggr_Bounds : Node_Id; Index_Bounds : Node_Id);
4014 -- Checks that the bounds of Aggr_Bounds are within the bounds defined
4015 -- by Index_Bounds.
4017 procedure Check_Same_Aggr_Bounds (Sub_Aggr : Node_Id; Dim : Pos);
4018 -- Checks that in a multi-dimensional array aggregate all subaggregates
4019 -- corresponding to the same dimension have the same bounds.
4020 -- Sub_Aggr is an array sub-aggregate. Dim is the dimension
4021 -- corresponding to the sub-aggregate.
4023 procedure Compute_Others_Present (Sub_Aggr : Node_Id; Dim : Pos);
4024 -- Computes the values of array Others_Present. Sub_Aggr is the
4025 -- array sub-aggregate we start the computation from. Dim is the
4026 -- dimension corresponding to the sub-aggregate.
4028 function Has_Address_Clause (D : Node_Id) return Boolean;
4029 -- If the aggregate is the expression in an object declaration, it
4030 -- cannot be expanded in place. This function does a lookahead in the
4031 -- current declarative part to find an address clause for the object
4032 -- being declared.
4034 function In_Place_Assign_OK return Boolean;
4035 -- Simple predicate to determine whether an aggregate assignment can
4036 -- be done in place, because none of the new values can depend on the
4037 -- components of the target of the assignment.
4039 procedure Others_Check (Sub_Aggr : Node_Id; Dim : Pos);
4040 -- Checks that if an others choice is present in any sub-aggregate no
4041 -- aggregate index is outside the bounds of the index constraint.
4042 -- Sub_Aggr is an array sub-aggregate. Dim is the dimension
4043 -- corresponding to the sub-aggregate.
4045 ----------------------------
4046 -- Build_Constrained_Type --
4047 ----------------------------
4049 procedure Build_Constrained_Type (Positional : Boolean) is
4050 Loc : constant Source_Ptr := Sloc (N);
4051 Agg_Type : Entity_Id;
4052 Comp : Node_Id;
4053 Decl : Node_Id;
4054 Typ : constant Entity_Id := Etype (N);
4055 Indices : constant List_Id := New_List;
4056 Num : Int;
4057 Sub_Agg : Node_Id;
4059 begin
4060 Agg_Type :=
4061 Make_Defining_Identifier (
4062 Loc, New_Internal_Name ('A'));
4064 -- If the aggregate is purely positional, all its subaggregates
4065 -- have the same size. We collect the dimensions from the first
4066 -- subaggregate at each level.
4068 if Positional then
4069 Sub_Agg := N;
4071 for D in 1 .. Number_Dimensions (Typ) loop
4072 Sub_Agg := First (Expressions (Sub_Agg));
4074 Comp := Sub_Agg;
4075 Num := 0;
4076 while Present (Comp) loop
4077 Num := Num + 1;
4078 Next (Comp);
4079 end loop;
4081 Append (
4082 Make_Range (Loc,
4083 Low_Bound => Make_Integer_Literal (Loc, 1),
4084 High_Bound =>
4085 Make_Integer_Literal (Loc, Num)),
4086 Indices);
4087 end loop;
4089 else
4090 -- We know the aggregate type is unconstrained and the aggregate
4091 -- is not processable by the back end, therefore not necessarily
4092 -- positional. Retrieve each dimension bounds (computed earlier).
4093 -- earlier.
4095 for D in 1 .. Number_Dimensions (Typ) loop
4096 Append (
4097 Make_Range (Loc,
4098 Low_Bound => Aggr_Low (D),
4099 High_Bound => Aggr_High (D)),
4100 Indices);
4101 end loop;
4102 end if;
4104 Decl :=
4105 Make_Full_Type_Declaration (Loc,
4106 Defining_Identifier => Agg_Type,
4107 Type_Definition =>
4108 Make_Constrained_Array_Definition (Loc,
4109 Discrete_Subtype_Definitions => Indices,
4110 Component_Definition =>
4111 Make_Component_Definition (Loc,
4112 Aliased_Present => False,
4113 Subtype_Indication =>
4114 New_Occurrence_Of (Component_Type (Typ), Loc))));
4116 Insert_Action (N, Decl);
4117 Analyze (Decl);
4118 Set_Etype (N, Agg_Type);
4119 Set_Is_Itype (Agg_Type);
4120 Freeze_Itype (Agg_Type, N);
4121 end Build_Constrained_Type;
4123 ------------------
4124 -- Check_Bounds --
4125 ------------------
4127 procedure Check_Bounds (Aggr_Bounds : Node_Id; Index_Bounds : Node_Id) is
4128 Aggr_Lo : Node_Id;
4129 Aggr_Hi : Node_Id;
4131 Ind_Lo : Node_Id;
4132 Ind_Hi : Node_Id;
4134 Cond : Node_Id := Empty;
4136 begin
4137 Get_Index_Bounds (Aggr_Bounds, Aggr_Lo, Aggr_Hi);
4138 Get_Index_Bounds (Index_Bounds, Ind_Lo, Ind_Hi);
4140 -- Generate the following test:
4142 -- [constraint_error when
4143 -- Aggr_Lo <= Aggr_Hi and then
4144 -- (Aggr_Lo < Ind_Lo or else Aggr_Hi > Ind_Hi)]
4146 -- As an optimization try to see if some tests are trivially vacuous
4147 -- because we are comparing an expression against itself.
4149 if Aggr_Lo = Ind_Lo and then Aggr_Hi = Ind_Hi then
4150 Cond := Empty;
4152 elsif Aggr_Hi = Ind_Hi then
4153 Cond :=
4154 Make_Op_Lt (Loc,
4155 Left_Opnd => Duplicate_Subexpr_Move_Checks (Aggr_Lo),
4156 Right_Opnd => Duplicate_Subexpr_Move_Checks (Ind_Lo));
4158 elsif Aggr_Lo = Ind_Lo then
4159 Cond :=
4160 Make_Op_Gt (Loc,
4161 Left_Opnd => Duplicate_Subexpr_Move_Checks (Aggr_Hi),
4162 Right_Opnd => Duplicate_Subexpr_Move_Checks (Ind_Hi));
4164 else
4165 Cond :=
4166 Make_Or_Else (Loc,
4167 Left_Opnd =>
4168 Make_Op_Lt (Loc,
4169 Left_Opnd => Duplicate_Subexpr_Move_Checks (Aggr_Lo),
4170 Right_Opnd => Duplicate_Subexpr_Move_Checks (Ind_Lo)),
4172 Right_Opnd =>
4173 Make_Op_Gt (Loc,
4174 Left_Opnd => Duplicate_Subexpr (Aggr_Hi),
4175 Right_Opnd => Duplicate_Subexpr (Ind_Hi)));
4176 end if;
4178 if Present (Cond) then
4179 Cond :=
4180 Make_And_Then (Loc,
4181 Left_Opnd =>
4182 Make_Op_Le (Loc,
4183 Left_Opnd => Duplicate_Subexpr_Move_Checks (Aggr_Lo),
4184 Right_Opnd => Duplicate_Subexpr_Move_Checks (Aggr_Hi)),
4186 Right_Opnd => Cond);
4188 Set_Analyzed (Left_Opnd (Left_Opnd (Cond)), False);
4189 Set_Analyzed (Right_Opnd (Left_Opnd (Cond)), False);
4190 Insert_Action (N,
4191 Make_Raise_Constraint_Error (Loc,
4192 Condition => Cond,
4193 Reason => CE_Length_Check_Failed));
4194 end if;
4195 end Check_Bounds;
4197 ----------------------------
4198 -- Check_Same_Aggr_Bounds --
4199 ----------------------------
4201 procedure Check_Same_Aggr_Bounds (Sub_Aggr : Node_Id; Dim : Pos) is
4202 Sub_Lo : constant Node_Id := Low_Bound (Aggregate_Bounds (Sub_Aggr));
4203 Sub_Hi : constant Node_Id := High_Bound (Aggregate_Bounds (Sub_Aggr));
4204 -- The bounds of this specific sub-aggregate
4206 Aggr_Lo : constant Node_Id := Aggr_Low (Dim);
4207 Aggr_Hi : constant Node_Id := Aggr_High (Dim);
4208 -- The bounds of the aggregate for this dimension
4210 Ind_Typ : constant Entity_Id := Aggr_Index_Typ (Dim);
4211 -- The index type for this dimension.xxx
4213 Cond : Node_Id := Empty;
4214 Assoc : Node_Id;
4215 Expr : Node_Id;
4217 begin
4218 -- If index checks are on generate the test
4220 -- [constraint_error when
4221 -- Aggr_Lo /= Sub_Lo or else Aggr_Hi /= Sub_Hi]
4223 -- As an optimization try to see if some tests are trivially vacuos
4224 -- because we are comparing an expression against itself. Also for
4225 -- the first dimension the test is trivially vacuous because there
4226 -- is just one aggregate for dimension 1.
4228 if Index_Checks_Suppressed (Ind_Typ) then
4229 Cond := Empty;
4231 elsif Dim = 1
4232 or else (Aggr_Lo = Sub_Lo and then Aggr_Hi = Sub_Hi)
4233 then
4234 Cond := Empty;
4236 elsif Aggr_Hi = Sub_Hi then
4237 Cond :=
4238 Make_Op_Ne (Loc,
4239 Left_Opnd => Duplicate_Subexpr_Move_Checks (Aggr_Lo),
4240 Right_Opnd => Duplicate_Subexpr_Move_Checks (Sub_Lo));
4242 elsif Aggr_Lo = Sub_Lo then
4243 Cond :=
4244 Make_Op_Ne (Loc,
4245 Left_Opnd => Duplicate_Subexpr_Move_Checks (Aggr_Hi),
4246 Right_Opnd => Duplicate_Subexpr_Move_Checks (Sub_Hi));
4248 else
4249 Cond :=
4250 Make_Or_Else (Loc,
4251 Left_Opnd =>
4252 Make_Op_Ne (Loc,
4253 Left_Opnd => Duplicate_Subexpr_Move_Checks (Aggr_Lo),
4254 Right_Opnd => Duplicate_Subexpr_Move_Checks (Sub_Lo)),
4256 Right_Opnd =>
4257 Make_Op_Ne (Loc,
4258 Left_Opnd => Duplicate_Subexpr (Aggr_Hi),
4259 Right_Opnd => Duplicate_Subexpr (Sub_Hi)));
4260 end if;
4262 if Present (Cond) then
4263 Insert_Action (N,
4264 Make_Raise_Constraint_Error (Loc,
4265 Condition => Cond,
4266 Reason => CE_Length_Check_Failed));
4267 end if;
4269 -- Now look inside the sub-aggregate to see if there is more work
4271 if Dim < Aggr_Dimension then
4273 -- Process positional components
4275 if Present (Expressions (Sub_Aggr)) then
4276 Expr := First (Expressions (Sub_Aggr));
4277 while Present (Expr) loop
4278 Check_Same_Aggr_Bounds (Expr, Dim + 1);
4279 Next (Expr);
4280 end loop;
4281 end if;
4283 -- Process component associations
4285 if Present (Component_Associations (Sub_Aggr)) then
4286 Assoc := First (Component_Associations (Sub_Aggr));
4287 while Present (Assoc) loop
4288 Expr := Expression (Assoc);
4289 Check_Same_Aggr_Bounds (Expr, Dim + 1);
4290 Next (Assoc);
4291 end loop;
4292 end if;
4293 end if;
4294 end Check_Same_Aggr_Bounds;
4296 ----------------------------
4297 -- Compute_Others_Present --
4298 ----------------------------
4300 procedure Compute_Others_Present (Sub_Aggr : Node_Id; Dim : Pos) is
4301 Assoc : Node_Id;
4302 Expr : Node_Id;
4304 begin
4305 if Present (Component_Associations (Sub_Aggr)) then
4306 Assoc := Last (Component_Associations (Sub_Aggr));
4308 if Nkind (First (Choices (Assoc))) = N_Others_Choice then
4309 Others_Present (Dim) := True;
4310 end if;
4311 end if;
4313 -- Now look inside the sub-aggregate to see if there is more work
4315 if Dim < Aggr_Dimension then
4317 -- Process positional components
4319 if Present (Expressions (Sub_Aggr)) then
4320 Expr := First (Expressions (Sub_Aggr));
4321 while Present (Expr) loop
4322 Compute_Others_Present (Expr, Dim + 1);
4323 Next (Expr);
4324 end loop;
4325 end if;
4327 -- Process component associations
4329 if Present (Component_Associations (Sub_Aggr)) then
4330 Assoc := First (Component_Associations (Sub_Aggr));
4331 while Present (Assoc) loop
4332 Expr := Expression (Assoc);
4333 Compute_Others_Present (Expr, Dim + 1);
4334 Next (Assoc);
4335 end loop;
4336 end if;
4337 end if;
4338 end Compute_Others_Present;
4340 ------------------------
4341 -- Has_Address_Clause --
4342 ------------------------
4344 function Has_Address_Clause (D : Node_Id) return Boolean is
4345 Id : constant Entity_Id := Defining_Identifier (D);
4346 Decl : Node_Id;
4348 begin
4349 Decl := Next (D);
4350 while Present (Decl) loop
4351 if Nkind (Decl) = N_At_Clause
4352 and then Chars (Identifier (Decl)) = Chars (Id)
4353 then
4354 return True;
4356 elsif Nkind (Decl) = N_Attribute_Definition_Clause
4357 and then Chars (Decl) = Name_Address
4358 and then Chars (Name (Decl)) = Chars (Id)
4359 then
4360 return True;
4361 end if;
4363 Next (Decl);
4364 end loop;
4366 return False;
4367 end Has_Address_Clause;
4369 ------------------------
4370 -- In_Place_Assign_OK --
4371 ------------------------
4373 function In_Place_Assign_OK return Boolean is
4374 Aggr_In : Node_Id;
4375 Aggr_Lo : Node_Id;
4376 Aggr_Hi : Node_Id;
4377 Obj_In : Node_Id;
4378 Obj_Lo : Node_Id;
4379 Obj_Hi : Node_Id;
4381 function Is_Others_Aggregate (Aggr : Node_Id) return Boolean;
4382 -- Aggregates that consist of a single Others choice are safe
4383 -- if the single expression is.
4385 function Safe_Aggregate (Aggr : Node_Id) return Boolean;
4386 -- Check recursively that each component of a (sub)aggregate does
4387 -- not depend on the variable being assigned to.
4389 function Safe_Component (Expr : Node_Id) return Boolean;
4390 -- Verify that an expression cannot depend on the variable being
4391 -- assigned to. Room for improvement here (but less than before).
4393 -------------------------
4394 -- Is_Others_Aggregate --
4395 -------------------------
4397 function Is_Others_Aggregate (Aggr : Node_Id) return Boolean is
4398 begin
4399 return No (Expressions (Aggr))
4400 and then Nkind
4401 (First (Choices (First (Component_Associations (Aggr)))))
4402 = N_Others_Choice;
4403 end Is_Others_Aggregate;
4405 --------------------
4406 -- Safe_Aggregate --
4407 --------------------
4409 function Safe_Aggregate (Aggr : Node_Id) return Boolean is
4410 Expr : Node_Id;
4412 begin
4413 if Present (Expressions (Aggr)) then
4414 Expr := First (Expressions (Aggr));
4415 while Present (Expr) loop
4416 if Nkind (Expr) = N_Aggregate then
4417 if not Safe_Aggregate (Expr) then
4418 return False;
4419 end if;
4421 elsif not Safe_Component (Expr) then
4422 return False;
4423 end if;
4425 Next (Expr);
4426 end loop;
4427 end if;
4429 if Present (Component_Associations (Aggr)) then
4430 Expr := First (Component_Associations (Aggr));
4431 while Present (Expr) loop
4432 if Nkind (Expression (Expr)) = N_Aggregate then
4433 if not Safe_Aggregate (Expression (Expr)) then
4434 return False;
4435 end if;
4437 elsif not Safe_Component (Expression (Expr)) then
4438 return False;
4439 end if;
4441 Next (Expr);
4442 end loop;
4443 end if;
4445 return True;
4446 end Safe_Aggregate;
4448 --------------------
4449 -- Safe_Component --
4450 --------------------
4452 function Safe_Component (Expr : Node_Id) return Boolean is
4453 Comp : Node_Id := Expr;
4455 function Check_Component (Comp : Node_Id) return Boolean;
4456 -- Do the recursive traversal, after copy
4458 ---------------------
4459 -- Check_Component --
4460 ---------------------
4462 function Check_Component (Comp : Node_Id) return Boolean is
4463 begin
4464 if Is_Overloaded (Comp) then
4465 return False;
4466 end if;
4468 return Compile_Time_Known_Value (Comp)
4470 or else (Is_Entity_Name (Comp)
4471 and then Present (Entity (Comp))
4472 and then No (Renamed_Object (Entity (Comp))))
4474 or else (Nkind (Comp) = N_Attribute_Reference
4475 and then Check_Component (Prefix (Comp)))
4477 or else (Nkind (Comp) in N_Binary_Op
4478 and then Check_Component (Left_Opnd (Comp))
4479 and then Check_Component (Right_Opnd (Comp)))
4481 or else (Nkind (Comp) in N_Unary_Op
4482 and then Check_Component (Right_Opnd (Comp)))
4484 or else (Nkind (Comp) = N_Selected_Component
4485 and then Check_Component (Prefix (Comp)))
4487 or else (Nkind (Comp) = N_Unchecked_Type_Conversion
4488 and then Check_Component (Expression (Comp)));
4489 end Check_Component;
4491 -- Start of processing for Safe_Component
4493 begin
4494 -- If the component appears in an association that may
4495 -- correspond to more than one element, it is not analyzed
4496 -- before the expansion into assignments, to avoid side effects.
4497 -- We analyze, but do not resolve the copy, to obtain sufficient
4498 -- entity information for the checks that follow. If component is
4499 -- overloaded we assume an unsafe function call.
4501 if not Analyzed (Comp) then
4502 if Is_Overloaded (Expr) then
4503 return False;
4505 elsif Nkind (Expr) = N_Aggregate
4506 and then not Is_Others_Aggregate (Expr)
4507 then
4508 return False;
4510 elsif Nkind (Expr) = N_Allocator then
4512 -- For now, too complex to analyze
4514 return False;
4515 end if;
4517 Comp := New_Copy_Tree (Expr);
4518 Set_Parent (Comp, Parent (Expr));
4519 Analyze (Comp);
4520 end if;
4522 if Nkind (Comp) = N_Aggregate then
4523 return Safe_Aggregate (Comp);
4524 else
4525 return Check_Component (Comp);
4526 end if;
4527 end Safe_Component;
4529 -- Start of processing for In_Place_Assign_OK
4531 begin
4532 if Present (Component_Associations (N)) then
4534 -- On assignment, sliding can take place, so we cannot do the
4535 -- assignment in place unless the bounds of the aggregate are
4536 -- statically equal to those of the target.
4538 -- If the aggregate is given by an others choice, the bounds
4539 -- are derived from the left-hand side, and the assignment is
4540 -- safe if the expression is.
4542 if Is_Others_Aggregate (N) then
4543 return
4544 Safe_Component
4545 (Expression (First (Component_Associations (N))));
4546 end if;
4548 Aggr_In := First_Index (Etype (N));
4549 if Nkind (Parent (N)) = N_Assignment_Statement then
4550 Obj_In := First_Index (Etype (Name (Parent (N))));
4552 else
4553 -- Context is an allocator. Check bounds of aggregate
4554 -- against given type in qualified expression.
4556 pragma Assert (Nkind (Parent (Parent (N))) = N_Allocator);
4557 Obj_In :=
4558 First_Index (Etype (Entity (Subtype_Mark (Parent (N)))));
4559 end if;
4561 while Present (Aggr_In) loop
4562 Get_Index_Bounds (Aggr_In, Aggr_Lo, Aggr_Hi);
4563 Get_Index_Bounds (Obj_In, Obj_Lo, Obj_Hi);
4565 if not Compile_Time_Known_Value (Aggr_Lo)
4566 or else not Compile_Time_Known_Value (Aggr_Hi)
4567 or else not Compile_Time_Known_Value (Obj_Lo)
4568 or else not Compile_Time_Known_Value (Obj_Hi)
4569 or else Expr_Value (Aggr_Lo) /= Expr_Value (Obj_Lo)
4570 or else Expr_Value (Aggr_Hi) /= Expr_Value (Obj_Hi)
4571 then
4572 return False;
4573 end if;
4575 Next_Index (Aggr_In);
4576 Next_Index (Obj_In);
4577 end loop;
4578 end if;
4580 -- Now check the component values themselves
4582 return Safe_Aggregate (N);
4583 end In_Place_Assign_OK;
4585 ------------------
4586 -- Others_Check --
4587 ------------------
4589 procedure Others_Check (Sub_Aggr : Node_Id; Dim : Pos) is
4590 Aggr_Lo : constant Node_Id := Aggr_Low (Dim);
4591 Aggr_Hi : constant Node_Id := Aggr_High (Dim);
4592 -- The bounds of the aggregate for this dimension
4594 Ind_Typ : constant Entity_Id := Aggr_Index_Typ (Dim);
4595 -- The index type for this dimension
4597 Need_To_Check : Boolean := False;
4599 Choices_Lo : Node_Id := Empty;
4600 Choices_Hi : Node_Id := Empty;
4601 -- The lowest and highest discrete choices for a named sub-aggregate
4603 Nb_Choices : Int := -1;
4604 -- The number of discrete non-others choices in this sub-aggregate
4606 Nb_Elements : Uint := Uint_0;
4607 -- The number of elements in a positional aggregate
4609 Cond : Node_Id := Empty;
4611 Assoc : Node_Id;
4612 Choice : Node_Id;
4613 Expr : Node_Id;
4615 begin
4616 -- Check if we have an others choice. If we do make sure that this
4617 -- sub-aggregate contains at least one element in addition to the
4618 -- others choice.
4620 if Range_Checks_Suppressed (Ind_Typ) then
4621 Need_To_Check := False;
4623 elsif Present (Expressions (Sub_Aggr))
4624 and then Present (Component_Associations (Sub_Aggr))
4625 then
4626 Need_To_Check := True;
4628 elsif Present (Component_Associations (Sub_Aggr)) then
4629 Assoc := Last (Component_Associations (Sub_Aggr));
4631 if Nkind (First (Choices (Assoc))) /= N_Others_Choice then
4632 Need_To_Check := False;
4634 else
4635 -- Count the number of discrete choices. Start with -1 because
4636 -- the others choice does not count.
4638 Nb_Choices := -1;
4639 Assoc := First (Component_Associations (Sub_Aggr));
4640 while Present (Assoc) loop
4641 Choice := First (Choices (Assoc));
4642 while Present (Choice) loop
4643 Nb_Choices := Nb_Choices + 1;
4644 Next (Choice);
4645 end loop;
4647 Next (Assoc);
4648 end loop;
4650 -- If there is only an others choice nothing to do
4652 Need_To_Check := (Nb_Choices > 0);
4653 end if;
4655 else
4656 Need_To_Check := False;
4657 end if;
4659 -- If we are dealing with a positional sub-aggregate with an others
4660 -- choice then compute the number or positional elements.
4662 if Need_To_Check and then Present (Expressions (Sub_Aggr)) then
4663 Expr := First (Expressions (Sub_Aggr));
4664 Nb_Elements := Uint_0;
4665 while Present (Expr) loop
4666 Nb_Elements := Nb_Elements + 1;
4667 Next (Expr);
4668 end loop;
4670 -- If the aggregate contains discrete choices and an others choice
4671 -- compute the smallest and largest discrete choice values.
4673 elsif Need_To_Check then
4674 Compute_Choices_Lo_And_Choices_Hi : declare
4676 Table : Case_Table_Type (1 .. Nb_Choices);
4677 -- Used to sort all the different choice values
4679 J : Pos := 1;
4680 Low : Node_Id;
4681 High : Node_Id;
4683 begin
4684 Assoc := First (Component_Associations (Sub_Aggr));
4685 while Present (Assoc) loop
4686 Choice := First (Choices (Assoc));
4687 while Present (Choice) loop
4688 if Nkind (Choice) = N_Others_Choice then
4689 exit;
4690 end if;
4692 Get_Index_Bounds (Choice, Low, High);
4693 Table (J).Choice_Lo := Low;
4694 Table (J).Choice_Hi := High;
4696 J := J + 1;
4697 Next (Choice);
4698 end loop;
4700 Next (Assoc);
4701 end loop;
4703 -- Sort the discrete choices
4705 Sort_Case_Table (Table);
4707 Choices_Lo := Table (1).Choice_Lo;
4708 Choices_Hi := Table (Nb_Choices).Choice_Hi;
4709 end Compute_Choices_Lo_And_Choices_Hi;
4710 end if;
4712 -- If no others choice in this sub-aggregate, or the aggregate
4713 -- comprises only an others choice, nothing to do.
4715 if not Need_To_Check then
4716 Cond := Empty;
4718 -- If we are dealing with an aggregate containing an others choice
4719 -- and positional components, we generate the following test:
4721 -- if Ind_Typ'Pos (Aggr_Lo) + (Nb_Elements - 1) >
4722 -- Ind_Typ'Pos (Aggr_Hi)
4723 -- then
4724 -- raise Constraint_Error;
4725 -- end if;
4727 elsif Nb_Elements > Uint_0 then
4728 Cond :=
4729 Make_Op_Gt (Loc,
4730 Left_Opnd =>
4731 Make_Op_Add (Loc,
4732 Left_Opnd =>
4733 Make_Attribute_Reference (Loc,
4734 Prefix => New_Reference_To (Ind_Typ, Loc),
4735 Attribute_Name => Name_Pos,
4736 Expressions =>
4737 New_List
4738 (Duplicate_Subexpr_Move_Checks (Aggr_Lo))),
4739 Right_Opnd => Make_Integer_Literal (Loc, Nb_Elements - 1)),
4741 Right_Opnd =>
4742 Make_Attribute_Reference (Loc,
4743 Prefix => New_Reference_To (Ind_Typ, Loc),
4744 Attribute_Name => Name_Pos,
4745 Expressions => New_List (
4746 Duplicate_Subexpr_Move_Checks (Aggr_Hi))));
4748 -- If we are dealing with an aggregate containing an others choice
4749 -- and discrete choices we generate the following test:
4751 -- [constraint_error when
4752 -- Choices_Lo < Aggr_Lo or else Choices_Hi > Aggr_Hi];
4754 else
4755 Cond :=
4756 Make_Or_Else (Loc,
4757 Left_Opnd =>
4758 Make_Op_Lt (Loc,
4759 Left_Opnd =>
4760 Duplicate_Subexpr_Move_Checks (Choices_Lo),
4761 Right_Opnd =>
4762 Duplicate_Subexpr_Move_Checks (Aggr_Lo)),
4764 Right_Opnd =>
4765 Make_Op_Gt (Loc,
4766 Left_Opnd =>
4767 Duplicate_Subexpr (Choices_Hi),
4768 Right_Opnd =>
4769 Duplicate_Subexpr (Aggr_Hi)));
4770 end if;
4772 if Present (Cond) then
4773 Insert_Action (N,
4774 Make_Raise_Constraint_Error (Loc,
4775 Condition => Cond,
4776 Reason => CE_Length_Check_Failed));
4777 -- Questionable reason code, shouldn't that be a
4778 -- CE_Range_Check_Failed ???
4779 end if;
4781 -- Now look inside the sub-aggregate to see if there is more work
4783 if Dim < Aggr_Dimension then
4785 -- Process positional components
4787 if Present (Expressions (Sub_Aggr)) then
4788 Expr := First (Expressions (Sub_Aggr));
4789 while Present (Expr) loop
4790 Others_Check (Expr, Dim + 1);
4791 Next (Expr);
4792 end loop;
4793 end if;
4795 -- Process component associations
4797 if Present (Component_Associations (Sub_Aggr)) then
4798 Assoc := First (Component_Associations (Sub_Aggr));
4799 while Present (Assoc) loop
4800 Expr := Expression (Assoc);
4801 Others_Check (Expr, Dim + 1);
4802 Next (Assoc);
4803 end loop;
4804 end if;
4805 end if;
4806 end Others_Check;
4808 -- Remaining Expand_Array_Aggregate variables
4810 Tmp : Entity_Id;
4811 -- Holds the temporary aggregate value
4813 Tmp_Decl : Node_Id;
4814 -- Holds the declaration of Tmp
4816 Aggr_Code : List_Id;
4817 Parent_Node : Node_Id;
4818 Parent_Kind : Node_Kind;
4820 -- Start of processing for Expand_Array_Aggregate
4822 begin
4823 -- Do not touch the special aggregates of attributes used for Asm calls
4825 if Is_RTE (Ctyp, RE_Asm_Input_Operand)
4826 or else Is_RTE (Ctyp, RE_Asm_Output_Operand)
4827 then
4828 return;
4829 end if;
4831 -- If the semantic analyzer has determined that aggregate N will raise
4832 -- Constraint_Error at run-time, then the aggregate node has been
4833 -- replaced with an N_Raise_Constraint_Error node and we should
4834 -- never get here.
4836 pragma Assert (not Raises_Constraint_Error (N));
4838 -- STEP 1a
4840 -- Check that the index range defined by aggregate bounds is
4841 -- compatible with corresponding index subtype.
4843 Index_Compatibility_Check : declare
4844 Aggr_Index_Range : Node_Id := First_Index (Typ);
4845 -- The current aggregate index range
4847 Index_Constraint : Node_Id := First_Index (Etype (Typ));
4848 -- The corresponding index constraint against which we have to
4849 -- check the above aggregate index range.
4851 begin
4852 Compute_Others_Present (N, 1);
4854 for J in 1 .. Aggr_Dimension loop
4855 -- There is no need to emit a check if an others choice is
4856 -- present for this array aggregate dimension since in this
4857 -- case one of N's sub-aggregates has taken its bounds from the
4858 -- context and these bounds must have been checked already. In
4859 -- addition all sub-aggregates corresponding to the same
4860 -- dimension must all have the same bounds (checked in (c) below).
4862 if not Range_Checks_Suppressed (Etype (Index_Constraint))
4863 and then not Others_Present (J)
4864 then
4865 -- We don't use Checks.Apply_Range_Check here because it emits
4866 -- a spurious check. Namely it checks that the range defined by
4867 -- the aggregate bounds is non empty. But we know this already
4868 -- if we get here.
4870 Check_Bounds (Aggr_Index_Range, Index_Constraint);
4871 end if;
4873 -- Save the low and high bounds of the aggregate index as well as
4874 -- the index type for later use in checks (b) and (c) below.
4876 Aggr_Low (J) := Low_Bound (Aggr_Index_Range);
4877 Aggr_High (J) := High_Bound (Aggr_Index_Range);
4879 Aggr_Index_Typ (J) := Etype (Index_Constraint);
4881 Next_Index (Aggr_Index_Range);
4882 Next_Index (Index_Constraint);
4883 end loop;
4884 end Index_Compatibility_Check;
4886 -- STEP 1b
4888 -- If an others choice is present check that no aggregate index is
4889 -- outside the bounds of the index constraint.
4891 Others_Check (N, 1);
4893 -- STEP 1c
4895 -- For multidimensional arrays make sure that all subaggregates
4896 -- corresponding to the same dimension have the same bounds.
4898 if Aggr_Dimension > 1 then
4899 Check_Same_Aggr_Bounds (N, 1);
4900 end if;
4902 -- STEP 2
4904 -- Here we test for is packed array aggregate that we can handle at
4905 -- compile time. If so, return with transformation done. Note that we do
4906 -- this even if the aggregate is nested, because once we have done this
4907 -- processing, there is no more nested aggregate!
4909 if Packed_Array_Aggregate_Handled (N) then
4910 return;
4911 end if;
4913 -- At this point we try to convert to positional form
4915 if Ekind (Current_Scope) = E_Package
4916 and then Static_Elaboration_Desired (Current_Scope)
4917 then
4918 Convert_To_Positional (N, Max_Others_Replicate => 100);
4920 else
4921 Convert_To_Positional (N);
4922 end if;
4924 -- if the result is no longer an aggregate (e.g. it may be a string
4925 -- literal, or a temporary which has the needed value), then we are
4926 -- done, since there is no longer a nested aggregate.
4928 if Nkind (N) /= N_Aggregate then
4929 return;
4931 -- We are also done if the result is an analyzed aggregate
4932 -- This case could use more comments ???
4934 elsif Analyzed (N)
4935 and then N /= Original_Node (N)
4936 then
4937 return;
4938 end if;
4940 -- If all aggregate components are compile-time known and the aggregate
4941 -- has been flattened, nothing left to do. The same occurs if the
4942 -- aggregate is used to initialize the components of an statically
4943 -- allocated dispatch table.
4945 if Compile_Time_Known_Aggregate (N)
4946 or else Is_Static_Dispatch_Table_Aggregate (N)
4947 then
4948 Set_Expansion_Delayed (N, False);
4949 return;
4950 end if;
4952 -- Now see if back end processing is possible
4954 if Backend_Processing_Possible (N) then
4956 -- If the aggregate is static but the constraints are not, build
4957 -- a static subtype for the aggregate, so that Gigi can place it
4958 -- in static memory. Perform an unchecked_conversion to the non-
4959 -- static type imposed by the context.
4961 declare
4962 Itype : constant Entity_Id := Etype (N);
4963 Index : Node_Id;
4964 Needs_Type : Boolean := False;
4966 begin
4967 Index := First_Index (Itype);
4968 while Present (Index) loop
4969 if not Is_Static_Subtype (Etype (Index)) then
4970 Needs_Type := True;
4971 exit;
4972 else
4973 Next_Index (Index);
4974 end if;
4975 end loop;
4977 if Needs_Type then
4978 Build_Constrained_Type (Positional => True);
4979 Rewrite (N, Unchecked_Convert_To (Itype, N));
4980 Analyze (N);
4981 end if;
4982 end;
4984 return;
4985 end if;
4987 -- STEP 3
4989 -- Delay expansion for nested aggregates: it will be taken care of
4990 -- when the parent aggregate is expanded.
4992 Parent_Node := Parent (N);
4993 Parent_Kind := Nkind (Parent_Node);
4995 if Parent_Kind = N_Qualified_Expression then
4996 Parent_Node := Parent (Parent_Node);
4997 Parent_Kind := Nkind (Parent_Node);
4998 end if;
5000 if Parent_Kind = N_Aggregate
5001 or else Parent_Kind = N_Extension_Aggregate
5002 or else Parent_Kind = N_Component_Association
5003 or else (Parent_Kind = N_Object_Declaration
5004 and then Needs_Finalization (Typ))
5005 or else (Parent_Kind = N_Assignment_Statement
5006 and then Inside_Init_Proc)
5007 then
5008 if Static_Array_Aggregate (N)
5009 or else Compile_Time_Known_Aggregate (N)
5010 then
5011 Set_Expansion_Delayed (N, False);
5012 return;
5013 else
5014 Set_Expansion_Delayed (N);
5015 return;
5016 end if;
5017 end if;
5019 -- STEP 4
5021 -- Look if in place aggregate expansion is possible
5023 -- For object declarations we build the aggregate in place, unless
5024 -- the array is bit-packed or the component is controlled.
5026 -- For assignments we do the assignment in place if all the component
5027 -- associations have compile-time known values. For other cases we
5028 -- create a temporary. The analysis for safety of on-line assignment
5029 -- is delicate, i.e. we don't know how to do it fully yet ???
5031 -- For allocators we assign to the designated object in place if the
5032 -- aggregate meets the same conditions as other in-place assignments.
5033 -- In this case the aggregate may not come from source but was created
5034 -- for default initialization, e.g. with Initialize_Scalars.
5036 if Requires_Transient_Scope (Typ) then
5037 Establish_Transient_Scope
5038 (N, Sec_Stack => Has_Controlled_Component (Typ));
5039 end if;
5041 if Has_Default_Init_Comps (N) then
5042 Maybe_In_Place_OK := False;
5044 elsif Is_Bit_Packed_Array (Typ)
5045 or else Has_Controlled_Component (Typ)
5046 then
5047 Maybe_In_Place_OK := False;
5049 else
5050 Maybe_In_Place_OK :=
5051 (Nkind (Parent (N)) = N_Assignment_Statement
5052 and then Comes_From_Source (N)
5053 and then In_Place_Assign_OK)
5055 or else
5056 (Nkind (Parent (Parent (N))) = N_Allocator
5057 and then In_Place_Assign_OK);
5058 end if;
5060 -- If this is an array of tasks, it will be expanded into build-in-place
5061 -- assignments. Build an activation chain for the tasks now.
5063 if Has_Task (Etype (N)) then
5064 Build_Activation_Chain_Entity (N);
5065 end if;
5067 if not Has_Default_Init_Comps (N)
5068 and then Comes_From_Source (Parent (N))
5069 and then Nkind (Parent (N)) = N_Object_Declaration
5070 and then not
5071 Must_Slide (Etype (Defining_Identifier (Parent (N))), Typ)
5072 and then N = Expression (Parent (N))
5073 and then not Is_Bit_Packed_Array (Typ)
5074 and then not Has_Controlled_Component (Typ)
5075 and then not Has_Address_Clause (Parent (N))
5076 then
5077 Tmp := Defining_Identifier (Parent (N));
5078 Set_No_Initialization (Parent (N));
5079 Set_Expression (Parent (N), Empty);
5081 -- Set the type of the entity, for use in the analysis of the
5082 -- subsequent indexed assignments. If the nominal type is not
5083 -- constrained, build a subtype from the known bounds of the
5084 -- aggregate. If the declaration has a subtype mark, use it,
5085 -- otherwise use the itype of the aggregate.
5087 if not Is_Constrained (Typ) then
5088 Build_Constrained_Type (Positional => False);
5089 elsif Is_Entity_Name (Object_Definition (Parent (N)))
5090 and then Is_Constrained (Entity (Object_Definition (Parent (N))))
5091 then
5092 Set_Etype (Tmp, Entity (Object_Definition (Parent (N))));
5093 else
5094 Set_Size_Known_At_Compile_Time (Typ, False);
5095 Set_Etype (Tmp, Typ);
5096 end if;
5098 elsif Maybe_In_Place_OK
5099 and then Nkind (Parent (N)) = N_Qualified_Expression
5100 and then Nkind (Parent (Parent (N))) = N_Allocator
5101 then
5102 Set_Expansion_Delayed (N);
5103 return;
5105 -- In the remaining cases the aggregate is the RHS of an assignment
5107 elsif Maybe_In_Place_OK
5108 and then Is_Entity_Name (Name (Parent (N)))
5109 then
5110 Tmp := Entity (Name (Parent (N)));
5112 if Etype (Tmp) /= Etype (N) then
5113 Apply_Length_Check (N, Etype (Tmp));
5115 if Nkind (N) = N_Raise_Constraint_Error then
5117 -- Static error, nothing further to expand
5119 return;
5120 end if;
5121 end if;
5123 elsif Maybe_In_Place_OK
5124 and then Nkind (Name (Parent (N))) = N_Explicit_Dereference
5125 and then Is_Entity_Name (Prefix (Name (Parent (N))))
5126 then
5127 Tmp := Name (Parent (N));
5129 if Etype (Tmp) /= Etype (N) then
5130 Apply_Length_Check (N, Etype (Tmp));
5131 end if;
5133 elsif Maybe_In_Place_OK
5134 and then Nkind (Name (Parent (N))) = N_Slice
5135 and then Safe_Slice_Assignment (N)
5136 then
5137 -- Safe_Slice_Assignment rewrites assignment as a loop
5139 return;
5141 -- Step 5
5143 -- In place aggregate expansion is not possible
5145 else
5146 Maybe_In_Place_OK := False;
5147 Tmp := Make_Defining_Identifier (Loc, New_Internal_Name ('A'));
5148 Tmp_Decl :=
5149 Make_Object_Declaration
5150 (Loc,
5151 Defining_Identifier => Tmp,
5152 Object_Definition => New_Occurrence_Of (Typ, Loc));
5153 Set_No_Initialization (Tmp_Decl, True);
5155 -- If we are within a loop, the temporary will be pushed on the
5156 -- stack at each iteration. If the aggregate is the expression for an
5157 -- allocator, it will be immediately copied to the heap and can
5158 -- be reclaimed at once. We create a transient scope around the
5159 -- aggregate for this purpose.
5161 if Ekind (Current_Scope) = E_Loop
5162 and then Nkind (Parent (Parent (N))) = N_Allocator
5163 then
5164 Establish_Transient_Scope (N, False);
5165 end if;
5167 Insert_Action (N, Tmp_Decl);
5168 end if;
5170 -- Construct and insert the aggregate code. We can safely suppress index
5171 -- checks because this code is guaranteed not to raise CE on index
5172 -- checks. However we should *not* suppress all checks.
5174 declare
5175 Target : Node_Id;
5177 begin
5178 if Nkind (Tmp) = N_Defining_Identifier then
5179 Target := New_Reference_To (Tmp, Loc);
5181 else
5183 if Has_Default_Init_Comps (N) then
5185 -- Ada 2005 (AI-287): This case has not been analyzed???
5187 raise Program_Error;
5188 end if;
5190 -- Name in assignment is explicit dereference
5192 Target := New_Copy (Tmp);
5193 end if;
5195 Aggr_Code :=
5196 Build_Array_Aggr_Code (N,
5197 Ctype => Ctyp,
5198 Index => First_Index (Typ),
5199 Into => Target,
5200 Scalar_Comp => Is_Scalar_Type (Ctyp));
5201 end;
5203 if Comes_From_Source (Tmp) then
5204 Insert_Actions_After (Parent (N), Aggr_Code);
5206 else
5207 Insert_Actions (N, Aggr_Code);
5208 end if;
5210 -- If the aggregate has been assigned in place, remove the original
5211 -- assignment.
5213 if Nkind (Parent (N)) = N_Assignment_Statement
5214 and then Maybe_In_Place_OK
5215 then
5216 Rewrite (Parent (N), Make_Null_Statement (Loc));
5218 elsif Nkind (Parent (N)) /= N_Object_Declaration
5219 or else Tmp /= Defining_Identifier (Parent (N))
5220 then
5221 Rewrite (N, New_Occurrence_Of (Tmp, Loc));
5222 Analyze_And_Resolve (N, Typ);
5223 end if;
5224 end Expand_Array_Aggregate;
5226 ------------------------
5227 -- Expand_N_Aggregate --
5228 ------------------------
5230 procedure Expand_N_Aggregate (N : Node_Id) is
5231 begin
5232 if Is_Record_Type (Etype (N)) then
5233 Expand_Record_Aggregate (N);
5234 else
5235 Expand_Array_Aggregate (N);
5236 end if;
5237 exception
5238 when RE_Not_Available =>
5239 return;
5240 end Expand_N_Aggregate;
5242 ----------------------------------
5243 -- Expand_N_Extension_Aggregate --
5244 ----------------------------------
5246 -- If the ancestor part is an expression, add a component association for
5247 -- the parent field. If the type of the ancestor part is not the direct
5248 -- parent of the expected type, build recursively the needed ancestors.
5249 -- If the ancestor part is a subtype_mark, replace aggregate with a decla-
5250 -- ration for a temporary of the expected type, followed by individual
5251 -- assignments to the given components.
5253 procedure Expand_N_Extension_Aggregate (N : Node_Id) is
5254 Loc : constant Source_Ptr := Sloc (N);
5255 A : constant Node_Id := Ancestor_Part (N);
5256 Typ : constant Entity_Id := Etype (N);
5258 begin
5259 -- If the ancestor is a subtype mark, an init proc must be called
5260 -- on the resulting object which thus has to be materialized in
5261 -- the front-end
5263 if Is_Entity_Name (A) and then Is_Type (Entity (A)) then
5264 Convert_To_Assignments (N, Typ);
5266 -- The extension aggregate is transformed into a record aggregate
5267 -- of the following form (c1 and c2 are inherited components)
5269 -- (Exp with c3 => a, c4 => b)
5270 -- ==> (c1 => Exp.c1, c2 => Exp.c2, c1 => a, c2 => b)
5272 else
5273 Set_Etype (N, Typ);
5275 if VM_Target = No_VM then
5276 Expand_Record_Aggregate (N,
5277 Orig_Tag =>
5278 New_Occurrence_Of
5279 (Node (First_Elmt (Access_Disp_Table (Typ))), Loc),
5280 Parent_Expr => A);
5281 else
5282 -- No tag is needed in the case of a VM
5283 Expand_Record_Aggregate (N,
5284 Parent_Expr => A);
5285 end if;
5286 end if;
5288 exception
5289 when RE_Not_Available =>
5290 return;
5291 end Expand_N_Extension_Aggregate;
5293 -----------------------------
5294 -- Expand_Record_Aggregate --
5295 -----------------------------
5297 procedure Expand_Record_Aggregate
5298 (N : Node_Id;
5299 Orig_Tag : Node_Id := Empty;
5300 Parent_Expr : Node_Id := Empty)
5302 Loc : constant Source_Ptr := Sloc (N);
5303 Comps : constant List_Id := Component_Associations (N);
5304 Typ : constant Entity_Id := Etype (N);
5305 Base_Typ : constant Entity_Id := Base_Type (Typ);
5307 Static_Components : Boolean := True;
5308 -- Flag to indicate whether all components are compile-time known,
5309 -- and the aggregate can be constructed statically and handled by
5310 -- the back-end.
5312 function Component_Not_OK_For_Backend return Boolean;
5313 -- Check for presence of component which makes it impossible for the
5314 -- backend to process the aggregate, thus requiring the use of a series
5315 -- of assignment statements. Cases checked for are a nested aggregate
5316 -- needing Late_Expansion, the presence of a tagged component which may
5317 -- need tag adjustment, and a bit unaligned component reference.
5319 -- We also force expansion into assignments if a component is of a
5320 -- mutable type (including a private type with discriminants) because
5321 -- in that case the size of the component to be copied may be smaller
5322 -- than the side of the target, and there is no simple way for gigi
5323 -- to compute the size of the object to be copied.
5325 -- NOTE: This is part of the ongoing work to define precisely the
5326 -- interface between front-end and back-end handling of aggregates.
5327 -- In general it is desirable to pass aggregates as they are to gigi,
5328 -- in order to minimize elaboration code. This is one case where the
5329 -- semantics of Ada complicate the analysis and lead to anomalies in
5330 -- the gcc back-end if the aggregate is not expanded into assignments.
5332 ----------------------------------
5333 -- Component_Not_OK_For_Backend --
5334 ----------------------------------
5336 function Component_Not_OK_For_Backend return Boolean is
5337 C : Node_Id;
5338 Expr_Q : Node_Id;
5340 begin
5341 if No (Comps) then
5342 return False;
5343 end if;
5345 C := First (Comps);
5346 while Present (C) loop
5347 if Nkind (Expression (C)) = N_Qualified_Expression then
5348 Expr_Q := Expression (Expression (C));
5349 else
5350 Expr_Q := Expression (C);
5351 end if;
5353 -- Return true if the aggregate has any associations for tagged
5354 -- components that may require tag adjustment.
5356 -- These are cases where the source expression may have a tag that
5357 -- could differ from the component tag (e.g., can occur for type
5358 -- conversions and formal parameters). (Tag adjustment not needed
5359 -- if VM_Target because object tags are implicit in the machine.)
5361 if Is_Tagged_Type (Etype (Expr_Q))
5362 and then (Nkind (Expr_Q) = N_Type_Conversion
5363 or else (Is_Entity_Name (Expr_Q)
5364 and then
5365 Ekind (Entity (Expr_Q)) in Formal_Kind))
5366 and then VM_Target = No_VM
5367 then
5368 Static_Components := False;
5369 return True;
5371 elsif Is_Delayed_Aggregate (Expr_Q) then
5372 Static_Components := False;
5373 return True;
5375 elsif Possible_Bit_Aligned_Component (Expr_Q) then
5376 Static_Components := False;
5377 return True;
5378 end if;
5380 if Is_Scalar_Type (Etype (Expr_Q)) then
5381 if not Compile_Time_Known_Value (Expr_Q) then
5382 Static_Components := False;
5383 end if;
5385 elsif Nkind (Expr_Q) /= N_Aggregate
5386 or else not Compile_Time_Known_Aggregate (Expr_Q)
5387 then
5388 Static_Components := False;
5390 if Is_Private_Type (Etype (Expr_Q))
5391 and then Has_Discriminants (Etype (Expr_Q))
5392 then
5393 return True;
5394 end if;
5395 end if;
5397 Next (C);
5398 end loop;
5400 return False;
5401 end Component_Not_OK_For_Backend;
5403 -- Remaining Expand_Record_Aggregate variables
5405 Tag_Value : Node_Id;
5406 Comp : Entity_Id;
5407 New_Comp : Node_Id;
5409 -- Start of processing for Expand_Record_Aggregate
5411 begin
5412 -- If the aggregate is to be assigned to an atomic variable, we
5413 -- have to prevent a piecemeal assignment even if the aggregate
5414 -- is to be expanded. We create a temporary for the aggregate, and
5415 -- assign the temporary instead, so that the back end can generate
5416 -- an atomic move for it.
5418 if Is_Atomic (Typ)
5419 and then Nkind_In (Parent (N), N_Object_Declaration,
5420 N_Assignment_Statement)
5421 and then Comes_From_Source (Parent (N))
5422 then
5423 Expand_Atomic_Aggregate (N, Typ);
5424 return;
5426 -- No special management required for aggregates used to initialize
5427 -- statically allocated dispatch tables
5429 elsif Is_Static_Dispatch_Table_Aggregate (N) then
5430 return;
5431 end if;
5433 -- Ada 2005 (AI-318-2): We need to convert to assignments if components
5434 -- are build-in-place function calls. This test could be more specific,
5435 -- but doing it for all inherently limited aggregates seems harmless.
5436 -- The assignments will turn into build-in-place function calls (see
5437 -- Make_Build_In_Place_Call_In_Assignment).
5439 if Ada_Version >= Ada_05 and then Is_Inherently_Limited_Type (Typ) then
5440 Convert_To_Assignments (N, Typ);
5442 -- Gigi doesn't handle properly temporaries of variable size
5443 -- so we generate it in the front-end
5445 elsif not Size_Known_At_Compile_Time (Typ) then
5446 Convert_To_Assignments (N, Typ);
5448 -- Temporaries for controlled aggregates need to be attached to a
5449 -- final chain in order to be properly finalized, so it has to
5450 -- be created in the front-end
5452 elsif Is_Controlled (Typ)
5453 or else Has_Controlled_Component (Base_Type (Typ))
5454 then
5455 Convert_To_Assignments (N, Typ);
5457 -- Ada 2005 (AI-287): In case of default initialized components we
5458 -- convert the aggregate into assignments.
5460 elsif Has_Default_Init_Comps (N) then
5461 Convert_To_Assignments (N, Typ);
5463 -- Check components
5465 elsif Component_Not_OK_For_Backend then
5466 Convert_To_Assignments (N, Typ);
5468 -- If an ancestor is private, some components are not inherited and
5469 -- we cannot expand into a record aggregate
5471 elsif Has_Private_Ancestor (Typ) then
5472 Convert_To_Assignments (N, Typ);
5474 -- ??? The following was done to compile fxacc00.ads in the ACVCs. Gigi
5475 -- is not able to handle the aggregate for Late_Request.
5477 elsif Is_Tagged_Type (Typ) and then Has_Discriminants (Typ) then
5478 Convert_To_Assignments (N, Typ);
5480 -- If the tagged types covers interface types we need to initialize all
5481 -- hidden components containing pointers to secondary dispatch tables.
5483 elsif Is_Tagged_Type (Typ) and then Has_Interfaces (Typ) then
5484 Convert_To_Assignments (N, Typ);
5486 -- If some components are mutable, the size of the aggregate component
5487 -- may be distinct from the default size of the type component, so
5488 -- we need to expand to insure that the back-end copies the proper
5489 -- size of the data.
5491 elsif Has_Mutable_Components (Typ) then
5492 Convert_To_Assignments (N, Typ);
5494 -- If the type involved has any non-bit aligned components, then we are
5495 -- not sure that the back end can handle this case correctly.
5497 elsif Type_May_Have_Bit_Aligned_Components (Typ) then
5498 Convert_To_Assignments (N, Typ);
5500 -- In all other cases, build a proper aggregate handlable by gigi
5502 else
5503 if Nkind (N) = N_Aggregate then
5505 -- If the aggregate is static and can be handled by the back-end,
5506 -- nothing left to do.
5508 if Static_Components then
5509 Set_Compile_Time_Known_Aggregate (N);
5510 Set_Expansion_Delayed (N, False);
5511 end if;
5512 end if;
5514 -- If no discriminants, nothing special to do
5516 if not Has_Discriminants (Typ) then
5517 null;
5519 -- Case of discriminants present
5521 elsif Is_Derived_Type (Typ) then
5523 -- For untagged types, non-stored discriminants are replaced
5524 -- with stored discriminants, which are the ones that gigi uses
5525 -- to describe the type and its components.
5527 Generate_Aggregate_For_Derived_Type : declare
5528 Constraints : constant List_Id := New_List;
5529 First_Comp : Node_Id;
5530 Discriminant : Entity_Id;
5531 Decl : Node_Id;
5532 Num_Disc : Int := 0;
5533 Num_Gird : Int := 0;
5535 procedure Prepend_Stored_Values (T : Entity_Id);
5536 -- Scan the list of stored discriminants of the type, and add
5537 -- their values to the aggregate being built.
5539 ---------------------------
5540 -- Prepend_Stored_Values --
5541 ---------------------------
5543 procedure Prepend_Stored_Values (T : Entity_Id) is
5544 begin
5545 Discriminant := First_Stored_Discriminant (T);
5546 while Present (Discriminant) loop
5547 New_Comp :=
5548 Make_Component_Association (Loc,
5549 Choices =>
5550 New_List (New_Occurrence_Of (Discriminant, Loc)),
5552 Expression =>
5553 New_Copy_Tree (
5554 Get_Discriminant_Value (
5555 Discriminant,
5556 Typ,
5557 Discriminant_Constraint (Typ))));
5559 if No (First_Comp) then
5560 Prepend_To (Component_Associations (N), New_Comp);
5561 else
5562 Insert_After (First_Comp, New_Comp);
5563 end if;
5565 First_Comp := New_Comp;
5566 Next_Stored_Discriminant (Discriminant);
5567 end loop;
5568 end Prepend_Stored_Values;
5570 -- Start of processing for Generate_Aggregate_For_Derived_Type
5572 begin
5573 -- Remove the associations for the discriminant of derived type
5575 First_Comp := First (Component_Associations (N));
5576 while Present (First_Comp) loop
5577 Comp := First_Comp;
5578 Next (First_Comp);
5580 if Ekind (Entity
5581 (First (Choices (Comp)))) = E_Discriminant
5582 then
5583 Remove (Comp);
5584 Num_Disc := Num_Disc + 1;
5585 end if;
5586 end loop;
5588 -- Insert stored discriminant associations in the correct
5589 -- order. If there are more stored discriminants than new
5590 -- discriminants, there is at least one new discriminant that
5591 -- constrains more than one of the stored discriminants. In
5592 -- this case we need to construct a proper subtype of the
5593 -- parent type, in order to supply values to all the
5594 -- components. Otherwise there is one-one correspondence
5595 -- between the constraints and the stored discriminants.
5597 First_Comp := Empty;
5599 Discriminant := First_Stored_Discriminant (Base_Type (Typ));
5600 while Present (Discriminant) loop
5601 Num_Gird := Num_Gird + 1;
5602 Next_Stored_Discriminant (Discriminant);
5603 end loop;
5605 -- Case of more stored discriminants than new discriminants
5607 if Num_Gird > Num_Disc then
5609 -- Create a proper subtype of the parent type, which is the
5610 -- proper implementation type for the aggregate, and convert
5611 -- it to the intended target type.
5613 Discriminant := First_Stored_Discriminant (Base_Type (Typ));
5614 while Present (Discriminant) loop
5615 New_Comp :=
5616 New_Copy_Tree (
5617 Get_Discriminant_Value (
5618 Discriminant,
5619 Typ,
5620 Discriminant_Constraint (Typ)));
5621 Append (New_Comp, Constraints);
5622 Next_Stored_Discriminant (Discriminant);
5623 end loop;
5625 Decl :=
5626 Make_Subtype_Declaration (Loc,
5627 Defining_Identifier =>
5628 Make_Defining_Identifier (Loc,
5629 New_Internal_Name ('T')),
5630 Subtype_Indication =>
5631 Make_Subtype_Indication (Loc,
5632 Subtype_Mark =>
5633 New_Occurrence_Of (Etype (Base_Type (Typ)), Loc),
5634 Constraint =>
5635 Make_Index_Or_Discriminant_Constraint
5636 (Loc, Constraints)));
5638 Insert_Action (N, Decl);
5639 Prepend_Stored_Values (Base_Type (Typ));
5641 Set_Etype (N, Defining_Identifier (Decl));
5642 Set_Analyzed (N);
5644 Rewrite (N, Unchecked_Convert_To (Typ, N));
5645 Analyze (N);
5647 -- Case where we do not have fewer new discriminants than
5648 -- stored discriminants, so in this case we can simply use the
5649 -- stored discriminants of the subtype.
5651 else
5652 Prepend_Stored_Values (Typ);
5653 end if;
5654 end Generate_Aggregate_For_Derived_Type;
5655 end if;
5657 if Is_Tagged_Type (Typ) then
5659 -- The tagged case, _parent and _tag component must be created
5661 -- Reset null_present unconditionally. tagged records always have
5662 -- at least one field (the tag or the parent)
5664 Set_Null_Record_Present (N, False);
5666 -- When the current aggregate comes from the expansion of an
5667 -- extension aggregate, the parent expr is replaced by an
5668 -- aggregate formed by selected components of this expr
5670 if Present (Parent_Expr)
5671 and then Is_Empty_List (Comps)
5672 then
5673 Comp := First_Component_Or_Discriminant (Typ);
5674 while Present (Comp) loop
5676 -- Skip all expander-generated components
5679 not Comes_From_Source (Original_Record_Component (Comp))
5680 then
5681 null;
5683 else
5684 New_Comp :=
5685 Make_Selected_Component (Loc,
5686 Prefix =>
5687 Unchecked_Convert_To (Typ,
5688 Duplicate_Subexpr (Parent_Expr, True)),
5690 Selector_Name => New_Occurrence_Of (Comp, Loc));
5692 Append_To (Comps,
5693 Make_Component_Association (Loc,
5694 Choices =>
5695 New_List (New_Occurrence_Of (Comp, Loc)),
5696 Expression =>
5697 New_Comp));
5699 Analyze_And_Resolve (New_Comp, Etype (Comp));
5700 end if;
5702 Next_Component_Or_Discriminant (Comp);
5703 end loop;
5704 end if;
5706 -- Compute the value for the Tag now, if the type is a root it
5707 -- will be included in the aggregate right away, otherwise it will
5708 -- be propagated to the parent aggregate
5710 if Present (Orig_Tag) then
5711 Tag_Value := Orig_Tag;
5712 elsif VM_Target /= No_VM then
5713 Tag_Value := Empty;
5714 else
5715 Tag_Value :=
5716 New_Occurrence_Of
5717 (Node (First_Elmt (Access_Disp_Table (Typ))), Loc);
5718 end if;
5720 -- For a derived type, an aggregate for the parent is formed with
5721 -- all the inherited components.
5723 if Is_Derived_Type (Typ) then
5725 declare
5726 First_Comp : Node_Id;
5727 Parent_Comps : List_Id;
5728 Parent_Aggr : Node_Id;
5729 Parent_Name : Node_Id;
5731 begin
5732 -- Remove the inherited component association from the
5733 -- aggregate and store them in the parent aggregate
5735 First_Comp := First (Component_Associations (N));
5736 Parent_Comps := New_List;
5737 while Present (First_Comp)
5738 and then Scope (Original_Record_Component (
5739 Entity (First (Choices (First_Comp))))) /= Base_Typ
5740 loop
5741 Comp := First_Comp;
5742 Next (First_Comp);
5743 Remove (Comp);
5744 Append (Comp, Parent_Comps);
5745 end loop;
5747 Parent_Aggr := Make_Aggregate (Loc,
5748 Component_Associations => Parent_Comps);
5749 Set_Etype (Parent_Aggr, Etype (Base_Type (Typ)));
5751 -- Find the _parent component
5753 Comp := First_Component (Typ);
5754 while Chars (Comp) /= Name_uParent loop
5755 Comp := Next_Component (Comp);
5756 end loop;
5758 Parent_Name := New_Occurrence_Of (Comp, Loc);
5760 -- Insert the parent aggregate
5762 Prepend_To (Component_Associations (N),
5763 Make_Component_Association (Loc,
5764 Choices => New_List (Parent_Name),
5765 Expression => Parent_Aggr));
5767 -- Expand recursively the parent propagating the right Tag
5769 Expand_Record_Aggregate (
5770 Parent_Aggr, Tag_Value, Parent_Expr);
5771 end;
5773 -- For a root type, the tag component is added (unless compiling
5774 -- for the VMs, where tags are implicit).
5776 elsif VM_Target = No_VM then
5777 declare
5778 Tag_Name : constant Node_Id :=
5779 New_Occurrence_Of
5780 (First_Tag_Component (Typ), Loc);
5781 Typ_Tag : constant Entity_Id := RTE (RE_Tag);
5782 Conv_Node : constant Node_Id :=
5783 Unchecked_Convert_To (Typ_Tag, Tag_Value);
5785 begin
5786 Set_Etype (Conv_Node, Typ_Tag);
5787 Prepend_To (Component_Associations (N),
5788 Make_Component_Association (Loc,
5789 Choices => New_List (Tag_Name),
5790 Expression => Conv_Node));
5791 end;
5792 end if;
5793 end if;
5794 end if;
5796 end Expand_Record_Aggregate;
5798 ----------------------------
5799 -- Has_Default_Init_Comps --
5800 ----------------------------
5802 function Has_Default_Init_Comps (N : Node_Id) return Boolean is
5803 Comps : constant List_Id := Component_Associations (N);
5804 C : Node_Id;
5805 Expr : Node_Id;
5806 begin
5807 pragma Assert (Nkind_In (N, N_Aggregate, N_Extension_Aggregate));
5809 if No (Comps) then
5810 return False;
5811 end if;
5813 if Has_Self_Reference (N) then
5814 return True;
5815 end if;
5817 -- Check if any direct component has default initialized components
5819 C := First (Comps);
5820 while Present (C) loop
5821 if Box_Present (C) then
5822 return True;
5823 end if;
5825 Next (C);
5826 end loop;
5828 -- Recursive call in case of aggregate expression
5830 C := First (Comps);
5831 while Present (C) loop
5832 Expr := Expression (C);
5834 if Present (Expr)
5835 and then
5836 Nkind_In (Expr, N_Aggregate, N_Extension_Aggregate)
5837 and then Has_Default_Init_Comps (Expr)
5838 then
5839 return True;
5840 end if;
5842 Next (C);
5843 end loop;
5845 return False;
5846 end Has_Default_Init_Comps;
5848 --------------------------
5849 -- Is_Delayed_Aggregate --
5850 --------------------------
5852 function Is_Delayed_Aggregate (N : Node_Id) return Boolean is
5853 Node : Node_Id := N;
5854 Kind : Node_Kind := Nkind (Node);
5856 begin
5857 if Kind = N_Qualified_Expression then
5858 Node := Expression (Node);
5859 Kind := Nkind (Node);
5860 end if;
5862 if Kind /= N_Aggregate and then Kind /= N_Extension_Aggregate then
5863 return False;
5864 else
5865 return Expansion_Delayed (Node);
5866 end if;
5867 end Is_Delayed_Aggregate;
5869 ----------------------------------------
5870 -- Is_Static_Dispatch_Table_Aggregate --
5871 ----------------------------------------
5873 function Is_Static_Dispatch_Table_Aggregate (N : Node_Id) return Boolean is
5874 Typ : constant Entity_Id := Base_Type (Etype (N));
5876 begin
5877 return Static_Dispatch_Tables
5878 and then VM_Target = No_VM
5879 and then RTU_Loaded (Ada_Tags)
5881 -- Avoid circularity when rebuilding the compiler
5883 and then Cunit_Entity (Get_Source_Unit (N)) /= RTU_Entity (Ada_Tags)
5884 and then (Typ = RTE (RE_Dispatch_Table_Wrapper)
5885 or else
5886 Typ = RTE (RE_Address_Array)
5887 or else
5888 Typ = RTE (RE_Type_Specific_Data)
5889 or else
5890 Typ = RTE (RE_Tag_Table)
5891 or else
5892 (RTE_Available (RE_Interface_Data)
5893 and then Typ = RTE (RE_Interface_Data))
5894 or else
5895 (RTE_Available (RE_Interfaces_Array)
5896 and then Typ = RTE (RE_Interfaces_Array))
5897 or else
5898 (RTE_Available (RE_Interface_Data_Element)
5899 and then Typ = RTE (RE_Interface_Data_Element)));
5900 end Is_Static_Dispatch_Table_Aggregate;
5902 --------------------
5903 -- Late_Expansion --
5904 --------------------
5906 function Late_Expansion
5907 (N : Node_Id;
5908 Typ : Entity_Id;
5909 Target : Node_Id;
5910 Flist : Node_Id := Empty;
5911 Obj : Entity_Id := Empty) return List_Id
5913 begin
5914 if Is_Record_Type (Etype (N)) then
5915 return Build_Record_Aggr_Code (N, Typ, Target, Flist, Obj);
5917 else pragma Assert (Is_Array_Type (Etype (N)));
5918 return
5919 Build_Array_Aggr_Code
5920 (N => N,
5921 Ctype => Component_Type (Etype (N)),
5922 Index => First_Index (Typ),
5923 Into => Target,
5924 Scalar_Comp => Is_Scalar_Type (Component_Type (Typ)),
5925 Indices => No_List,
5926 Flist => Flist);
5927 end if;
5928 end Late_Expansion;
5930 ----------------------------------
5931 -- Make_OK_Assignment_Statement --
5932 ----------------------------------
5934 function Make_OK_Assignment_Statement
5935 (Sloc : Source_Ptr;
5936 Name : Node_Id;
5937 Expression : Node_Id) return Node_Id
5939 begin
5940 Set_Assignment_OK (Name);
5942 return Make_Assignment_Statement (Sloc, Name, Expression);
5943 end Make_OK_Assignment_Statement;
5945 -----------------------
5946 -- Number_Of_Choices --
5947 -----------------------
5949 function Number_Of_Choices (N : Node_Id) return Nat is
5950 Assoc : Node_Id;
5951 Choice : Node_Id;
5953 Nb_Choices : Nat := 0;
5955 begin
5956 if Present (Expressions (N)) then
5957 return 0;
5958 end if;
5960 Assoc := First (Component_Associations (N));
5961 while Present (Assoc) loop
5962 Choice := First (Choices (Assoc));
5963 while Present (Choice) loop
5964 if Nkind (Choice) /= N_Others_Choice then
5965 Nb_Choices := Nb_Choices + 1;
5966 end if;
5968 Next (Choice);
5969 end loop;
5971 Next (Assoc);
5972 end loop;
5974 return Nb_Choices;
5975 end Number_Of_Choices;
5977 ------------------------------------
5978 -- Packed_Array_Aggregate_Handled --
5979 ------------------------------------
5981 -- The current version of this procedure will handle at compile time
5982 -- any array aggregate that meets these conditions:
5984 -- One dimensional, bit packed
5985 -- Underlying packed type is modular type
5986 -- Bounds are within 32-bit Int range
5987 -- All bounds and values are static
5989 function Packed_Array_Aggregate_Handled (N : Node_Id) return Boolean is
5990 Loc : constant Source_Ptr := Sloc (N);
5991 Typ : constant Entity_Id := Etype (N);
5992 Ctyp : constant Entity_Id := Component_Type (Typ);
5994 Not_Handled : exception;
5995 -- Exception raised if this aggregate cannot be handled
5997 begin
5998 -- For now, handle only one dimensional bit packed arrays
6000 if not Is_Bit_Packed_Array (Typ)
6001 or else Number_Dimensions (Typ) > 1
6002 or else not Is_Modular_Integer_Type (Packed_Array_Type (Typ))
6003 then
6004 return False;
6005 end if;
6007 if not Is_Scalar_Type (Component_Type (Typ))
6008 and then Has_Non_Standard_Rep (Component_Type (Typ))
6009 then
6010 return False;
6011 end if;
6013 declare
6014 Csiz : constant Nat := UI_To_Int (Component_Size (Typ));
6016 Lo : Node_Id;
6017 Hi : Node_Id;
6018 -- Bounds of index type
6020 Lob : Uint;
6021 Hib : Uint;
6022 -- Values of bounds if compile time known
6024 function Get_Component_Val (N : Node_Id) return Uint;
6025 -- Given a expression value N of the component type Ctyp, returns a
6026 -- value of Csiz (component size) bits representing this value. If
6027 -- the value is non-static or any other reason exists why the value
6028 -- cannot be returned, then Not_Handled is raised.
6030 -----------------------
6031 -- Get_Component_Val --
6032 -----------------------
6034 function Get_Component_Val (N : Node_Id) return Uint is
6035 Val : Uint;
6037 begin
6038 -- We have to analyze the expression here before doing any further
6039 -- processing here. The analysis of such expressions is deferred
6040 -- till expansion to prevent some problems of premature analysis.
6042 Analyze_And_Resolve (N, Ctyp);
6044 -- Must have a compile time value. String literals have to be
6045 -- converted into temporaries as well, because they cannot easily
6046 -- be converted into their bit representation.
6048 if not Compile_Time_Known_Value (N)
6049 or else Nkind (N) = N_String_Literal
6050 then
6051 raise Not_Handled;
6052 end if;
6054 Val := Expr_Rep_Value (N);
6056 -- Adjust for bias, and strip proper number of bits
6058 if Has_Biased_Representation (Ctyp) then
6059 Val := Val - Expr_Value (Type_Low_Bound (Ctyp));
6060 end if;
6062 return Val mod Uint_2 ** Csiz;
6063 end Get_Component_Val;
6065 -- Here we know we have a one dimensional bit packed array
6067 begin
6068 Get_Index_Bounds (First_Index (Typ), Lo, Hi);
6070 -- Cannot do anything if bounds are dynamic
6072 if not Compile_Time_Known_Value (Lo)
6073 or else
6074 not Compile_Time_Known_Value (Hi)
6075 then
6076 return False;
6077 end if;
6079 -- Or are silly out of range of int bounds
6081 Lob := Expr_Value (Lo);
6082 Hib := Expr_Value (Hi);
6084 if not UI_Is_In_Int_Range (Lob)
6085 or else
6086 not UI_Is_In_Int_Range (Hib)
6087 then
6088 return False;
6089 end if;
6091 -- At this stage we have a suitable aggregate for handling at compile
6092 -- time (the only remaining checks are that the values of expressions
6093 -- in the aggregate are compile time known (check is performed by
6094 -- Get_Component_Val), and that any subtypes or ranges are statically
6095 -- known.
6097 -- If the aggregate is not fully positional at this stage, then
6098 -- convert it to positional form. Either this will fail, in which
6099 -- case we can do nothing, or it will succeed, in which case we have
6100 -- succeeded in handling the aggregate, or it will stay an aggregate,
6101 -- in which case we have failed to handle this case.
6103 if Present (Component_Associations (N)) then
6104 Convert_To_Positional
6105 (N, Max_Others_Replicate => 64, Handle_Bit_Packed => True);
6106 return Nkind (N) /= N_Aggregate;
6107 end if;
6109 -- Otherwise we are all positional, so convert to proper value
6111 declare
6112 Lov : constant Int := UI_To_Int (Lob);
6113 Hiv : constant Int := UI_To_Int (Hib);
6115 Len : constant Nat := Int'Max (0, Hiv - Lov + 1);
6116 -- The length of the array (number of elements)
6118 Aggregate_Val : Uint;
6119 -- Value of aggregate. The value is set in the low order bits of
6120 -- this value. For the little-endian case, the values are stored
6121 -- from low-order to high-order and for the big-endian case the
6122 -- values are stored from high-order to low-order. Note that gigi
6123 -- will take care of the conversions to left justify the value in
6124 -- the big endian case (because of left justified modular type
6125 -- processing), so we do not have to worry about that here.
6127 Lit : Node_Id;
6128 -- Integer literal for resulting constructed value
6130 Shift : Nat;
6131 -- Shift count from low order for next value
6133 Incr : Int;
6134 -- Shift increment for loop
6136 Expr : Node_Id;
6137 -- Next expression from positional parameters of aggregate
6139 begin
6140 -- For little endian, we fill up the low order bits of the target
6141 -- value. For big endian we fill up the high order bits of the
6142 -- target value (which is a left justified modular value).
6144 if Bytes_Big_Endian xor Debug_Flag_8 then
6145 Shift := Csiz * (Len - 1);
6146 Incr := -Csiz;
6147 else
6148 Shift := 0;
6149 Incr := +Csiz;
6150 end if;
6152 -- Loop to set the values
6154 if Len = 0 then
6155 Aggregate_Val := Uint_0;
6156 else
6157 Expr := First (Expressions (N));
6158 Aggregate_Val := Get_Component_Val (Expr) * Uint_2 ** Shift;
6160 for J in 2 .. Len loop
6161 Shift := Shift + Incr;
6162 Next (Expr);
6163 Aggregate_Val :=
6164 Aggregate_Val + Get_Component_Val (Expr) * Uint_2 ** Shift;
6165 end loop;
6166 end if;
6168 -- Now we can rewrite with the proper value
6170 Lit :=
6171 Make_Integer_Literal (Loc,
6172 Intval => Aggregate_Val);
6173 Set_Print_In_Hex (Lit);
6175 -- Construct the expression using this literal. Note that it is
6176 -- important to qualify the literal with its proper modular type
6177 -- since universal integer does not have the required range and
6178 -- also this is a left justified modular type, which is important
6179 -- in the big-endian case.
6181 Rewrite (N,
6182 Unchecked_Convert_To (Typ,
6183 Make_Qualified_Expression (Loc,
6184 Subtype_Mark =>
6185 New_Occurrence_Of (Packed_Array_Type (Typ), Loc),
6186 Expression => Lit)));
6188 Analyze_And_Resolve (N, Typ);
6189 return True;
6190 end;
6191 end;
6193 exception
6194 when Not_Handled =>
6195 return False;
6196 end Packed_Array_Aggregate_Handled;
6198 ----------------------------
6199 -- Has_Mutable_Components --
6200 ----------------------------
6202 function Has_Mutable_Components (Typ : Entity_Id) return Boolean is
6203 Comp : Entity_Id;
6205 begin
6206 Comp := First_Component (Typ);
6207 while Present (Comp) loop
6208 if Is_Record_Type (Etype (Comp))
6209 and then Has_Discriminants (Etype (Comp))
6210 and then not Is_Constrained (Etype (Comp))
6211 then
6212 return True;
6213 end if;
6215 Next_Component (Comp);
6216 end loop;
6218 return False;
6219 end Has_Mutable_Components;
6221 ------------------------------
6222 -- Initialize_Discriminants --
6223 ------------------------------
6225 procedure Initialize_Discriminants (N : Node_Id; Typ : Entity_Id) is
6226 Loc : constant Source_Ptr := Sloc (N);
6227 Bas : constant Entity_Id := Base_Type (Typ);
6228 Par : constant Entity_Id := Etype (Bas);
6229 Decl : constant Node_Id := Parent (Par);
6230 Ref : Node_Id;
6232 begin
6233 if Is_Tagged_Type (Bas)
6234 and then Is_Derived_Type (Bas)
6235 and then Has_Discriminants (Par)
6236 and then Has_Discriminants (Bas)
6237 and then Number_Discriminants (Bas) /= Number_Discriminants (Par)
6238 and then Nkind (Decl) = N_Full_Type_Declaration
6239 and then Nkind (Type_Definition (Decl)) = N_Record_Definition
6240 and then Present
6241 (Variant_Part (Component_List (Type_Definition (Decl))))
6242 and then Nkind (N) /= N_Extension_Aggregate
6243 then
6245 -- Call init proc to set discriminants.
6246 -- There should eventually be a special procedure for this ???
6248 Ref := New_Reference_To (Defining_Identifier (N), Loc);
6249 Insert_Actions_After (N,
6250 Build_Initialization_Call (Sloc (N), Ref, Typ));
6251 end if;
6252 end Initialize_Discriminants;
6254 ----------------
6255 -- Must_Slide --
6256 ----------------
6258 function Must_Slide
6259 (Obj_Type : Entity_Id;
6260 Typ : Entity_Id) return Boolean
6262 L1, L2, H1, H2 : Node_Id;
6263 begin
6264 -- No sliding if the type of the object is not established yet, if it is
6265 -- an unconstrained type whose actual subtype comes from the aggregate,
6266 -- or if the two types are identical.
6268 if not Is_Array_Type (Obj_Type) then
6269 return False;
6271 elsif not Is_Constrained (Obj_Type) then
6272 return False;
6274 elsif Typ = Obj_Type then
6275 return False;
6277 else
6278 -- Sliding can only occur along the first dimension
6280 Get_Index_Bounds (First_Index (Typ), L1, H1);
6281 Get_Index_Bounds (First_Index (Obj_Type), L2, H2);
6283 if not Is_Static_Expression (L1)
6284 or else not Is_Static_Expression (L2)
6285 or else not Is_Static_Expression (H1)
6286 or else not Is_Static_Expression (H2)
6287 then
6288 return False;
6289 else
6290 return Expr_Value (L1) /= Expr_Value (L2)
6291 or else Expr_Value (H1) /= Expr_Value (H2);
6292 end if;
6293 end if;
6294 end Must_Slide;
6296 ---------------------------
6297 -- Safe_Slice_Assignment --
6298 ---------------------------
6300 function Safe_Slice_Assignment (N : Node_Id) return Boolean is
6301 Loc : constant Source_Ptr := Sloc (Parent (N));
6302 Pref : constant Node_Id := Prefix (Name (Parent (N)));
6303 Range_Node : constant Node_Id := Discrete_Range (Name (Parent (N)));
6304 Expr : Node_Id;
6305 L_J : Entity_Id;
6306 L_Iter : Node_Id;
6307 L_Body : Node_Id;
6308 Stat : Node_Id;
6310 begin
6311 -- Generate: for J in Range loop Pref (J) := Expr; end loop;
6313 if Comes_From_Source (N)
6314 and then No (Expressions (N))
6315 and then Nkind (First (Choices (First (Component_Associations (N)))))
6316 = N_Others_Choice
6317 then
6318 Expr :=
6319 Expression (First (Component_Associations (N)));
6320 L_J := Make_Defining_Identifier (Loc, New_Internal_Name ('J'));
6322 L_Iter :=
6323 Make_Iteration_Scheme (Loc,
6324 Loop_Parameter_Specification =>
6325 Make_Loop_Parameter_Specification
6326 (Loc,
6327 Defining_Identifier => L_J,
6328 Discrete_Subtype_Definition => Relocate_Node (Range_Node)));
6330 L_Body :=
6331 Make_Assignment_Statement (Loc,
6332 Name =>
6333 Make_Indexed_Component (Loc,
6334 Prefix => Relocate_Node (Pref),
6335 Expressions => New_List (New_Occurrence_Of (L_J, Loc))),
6336 Expression => Relocate_Node (Expr));
6338 -- Construct the final loop
6340 Stat :=
6341 Make_Implicit_Loop_Statement
6342 (Node => Parent (N),
6343 Identifier => Empty,
6344 Iteration_Scheme => L_Iter,
6345 Statements => New_List (L_Body));
6347 -- Set type of aggregate to be type of lhs in assignment,
6348 -- to suppress redundant length checks.
6350 Set_Etype (N, Etype (Name (Parent (N))));
6352 Rewrite (Parent (N), Stat);
6353 Analyze (Parent (N));
6354 return True;
6356 else
6357 return False;
6358 end if;
6359 end Safe_Slice_Assignment;
6361 ---------------------
6362 -- Sort_Case_Table --
6363 ---------------------
6365 procedure Sort_Case_Table (Case_Table : in out Case_Table_Type) is
6366 L : constant Int := Case_Table'First;
6367 U : constant Int := Case_Table'Last;
6368 K : Int;
6369 J : Int;
6370 T : Case_Bounds;
6372 begin
6373 K := L;
6374 while K /= U loop
6375 T := Case_Table (K + 1);
6377 J := K + 1;
6378 while J /= L
6379 and then Expr_Value (Case_Table (J - 1).Choice_Lo) >
6380 Expr_Value (T.Choice_Lo)
6381 loop
6382 Case_Table (J) := Case_Table (J - 1);
6383 J := J - 1;
6384 end loop;
6386 Case_Table (J) := T;
6387 K := K + 1;
6388 end loop;
6389 end Sort_Case_Table;
6391 ----------------------------
6392 -- Static_Array_Aggregate --
6393 ----------------------------
6395 function Static_Array_Aggregate (N : Node_Id) return Boolean is
6396 Bounds : constant Node_Id := Aggregate_Bounds (N);
6398 Typ : constant Entity_Id := Etype (N);
6399 Comp_Type : constant Entity_Id := Component_Type (Typ);
6400 Agg : Node_Id;
6401 Expr : Node_Id;
6402 Lo : Node_Id;
6403 Hi : Node_Id;
6405 begin
6406 if Is_Tagged_Type (Typ)
6407 or else Is_Controlled (Typ)
6408 or else Is_Packed (Typ)
6409 then
6410 return False;
6411 end if;
6413 if Present (Bounds)
6414 and then Nkind (Bounds) = N_Range
6415 and then Nkind (Low_Bound (Bounds)) = N_Integer_Literal
6416 and then Nkind (High_Bound (Bounds)) = N_Integer_Literal
6417 then
6418 Lo := Low_Bound (Bounds);
6419 Hi := High_Bound (Bounds);
6421 if No (Component_Associations (N)) then
6423 -- Verify that all components are static integers
6425 Expr := First (Expressions (N));
6426 while Present (Expr) loop
6427 if Nkind (Expr) /= N_Integer_Literal then
6428 return False;
6429 end if;
6431 Next (Expr);
6432 end loop;
6434 return True;
6436 else
6437 -- We allow only a single named association, either a static
6438 -- range or an others_clause, with a static expression.
6440 Expr := First (Component_Associations (N));
6442 if Present (Expressions (N)) then
6443 return False;
6445 elsif Present (Next (Expr)) then
6446 return False;
6448 elsif Present (Next (First (Choices (Expr)))) then
6449 return False;
6451 else
6452 -- The aggregate is static if all components are literals,
6453 -- or else all its components are static aggregates for the
6454 -- component type. We also limit the size of a static aggregate
6455 -- to prevent runaway static expressions.
6457 if Is_Array_Type (Comp_Type)
6458 or else Is_Record_Type (Comp_Type)
6459 then
6460 if Nkind (Expression (Expr)) /= N_Aggregate
6461 or else
6462 not Compile_Time_Known_Aggregate (Expression (Expr))
6463 then
6464 return False;
6465 end if;
6467 elsif Nkind (Expression (Expr)) /= N_Integer_Literal then
6468 return False;
6470 elsif not Aggr_Size_OK (N, Typ) then
6471 return False;
6472 end if;
6474 -- Create a positional aggregate with the right number of
6475 -- copies of the expression.
6477 Agg := Make_Aggregate (Sloc (N), New_List, No_List);
6479 for I in UI_To_Int (Intval (Lo)) .. UI_To_Int (Intval (Hi))
6480 loop
6481 Append_To
6482 (Expressions (Agg), New_Copy (Expression (Expr)));
6484 -- The copied expression must be analyzed and resolved.
6485 -- Besides setting the type, this ensures that static
6486 -- expressions are appropriately marked as such.
6488 Analyze_And_Resolve
6489 (Last (Expressions (Agg)), Component_Type (Typ));
6490 end loop;
6492 Set_Aggregate_Bounds (Agg, Bounds);
6493 Set_Etype (Agg, Typ);
6494 Set_Analyzed (Agg);
6495 Rewrite (N, Agg);
6496 Set_Compile_Time_Known_Aggregate (N);
6498 return True;
6499 end if;
6500 end if;
6502 else
6503 return False;
6504 end if;
6505 end Static_Array_Aggregate;
6507 end Exp_Aggr;