merge with trunk @ 139506
[official-gcc.git] / gcc / ada / exp_aggr.adb
blobdf5617a09fc627a4cc83dba7026e87858331f71f
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-2008, 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 Freeze; use Freeze;
39 with Itypes; use Itypes;
40 with Lib; use Lib;
41 with Namet; use Namet;
42 with Nmake; use Nmake;
43 with Nlists; use Nlists;
44 with Opt; use Opt;
45 with Restrict; use Restrict;
46 with Rident; use Rident;
47 with Rtsfind; use Rtsfind;
48 with Ttypes; use Ttypes;
49 with Sem; use Sem;
50 with Sem_Ch3; use Sem_Ch3;
51 with Sem_Eval; use Sem_Eval;
52 with Sem_Res; use Sem_Res;
53 with Sem_Util; use Sem_Util;
54 with Sinfo; use Sinfo;
55 with Snames; use Snames;
56 with Stand; use Stand;
57 with Targparm; use Targparm;
58 with Tbuild; use Tbuild;
59 with Uintp; use Uintp;
61 package body Exp_Aggr is
63 type Case_Bounds is record
64 Choice_Lo : Node_Id;
65 Choice_Hi : Node_Id;
66 Choice_Node : Node_Id;
67 end record;
69 type Case_Table_Type is array (Nat range <>) of Case_Bounds;
70 -- Table type used by Check_Case_Choices procedure
72 function Must_Slide
73 (Obj_Type : Entity_Id;
74 Typ : Entity_Id) return Boolean;
75 -- A static array aggregate in an object declaration can in most cases be
76 -- expanded in place. The one exception is when the aggregate is given
77 -- with component associations that specify different bounds from those of
78 -- the type definition in the object declaration. In this pathological
79 -- case the aggregate must slide, and we must introduce an intermediate
80 -- temporary to hold it.
82 -- The same holds in an assignment to one-dimensional array of arrays,
83 -- when a component may be given with bounds that differ from those of the
84 -- component type.
86 procedure Sort_Case_Table (Case_Table : in out Case_Table_Type);
87 -- Sort the Case Table using the Lower Bound of each Choice as the key.
88 -- A simple insertion sort is used since the number of choices in a case
89 -- statement of variant part will usually be small and probably in near
90 -- sorted order.
92 function Has_Default_Init_Comps (N : Node_Id) return Boolean;
93 -- N is an aggregate (record or array). Checks the presence of default
94 -- initialization (<>) in any component (Ada 2005: AI-287)
96 function Is_Static_Dispatch_Table_Aggregate (N : Node_Id) return Boolean;
97 -- Returns true if N is an aggregate used to initialize the components
98 -- of an statically allocated dispatch table.
100 ------------------------------------------------------
101 -- Local subprograms for Record Aggregate Expansion --
102 ------------------------------------------------------
104 procedure Expand_Record_Aggregate
105 (N : Node_Id;
106 Orig_Tag : Node_Id := Empty;
107 Parent_Expr : Node_Id := Empty);
108 -- This is the top level procedure for record aggregate expansion.
109 -- Expansion for record aggregates needs expand aggregates for tagged
110 -- record types. Specifically Expand_Record_Aggregate adds the Tag
111 -- field in front of the Component_Association list that was created
112 -- during resolution by Resolve_Record_Aggregate.
114 -- N is the record aggregate node.
115 -- Orig_Tag is the value of the Tag that has to be provided for this
116 -- specific aggregate. It carries the tag corresponding to the type
117 -- of the outermost aggregate during the recursive expansion
118 -- Parent_Expr is the ancestor part of the original extension
119 -- aggregate
121 procedure Convert_To_Assignments (N : Node_Id; Typ : Entity_Id);
122 -- N is an N_Aggregate or an N_Extension_Aggregate. Typ is the type of the
123 -- aggregate (which can only be a record type, this procedure is only used
124 -- for record types). Transform the given aggregate into a sequence of
125 -- assignments performed component by component.
127 function Build_Record_Aggr_Code
128 (N : Node_Id;
129 Typ : Entity_Id;
130 Lhs : Node_Id;
131 Flist : Node_Id := Empty;
132 Obj : Entity_Id := Empty;
133 Is_Limited_Ancestor_Expansion : Boolean := False) return List_Id;
134 -- N is an N_Aggregate or an N_Extension_Aggregate. Typ is the type of the
135 -- aggregate. Target is an expression containing the location on which the
136 -- component by component assignments will take place. Returns the list of
137 -- assignments plus all other adjustments needed for tagged and controlled
138 -- types. Flist is an expression representing the finalization list on
139 -- which to attach the controlled components if any. Obj is present in the
140 -- object declaration and dynamic allocation cases, it contains an entity
141 -- that allows to know if the value being created needs to be attached to
142 -- the final list in case of pragma Finalize_Storage_Only.
144 -- ???
145 -- The meaning of the Obj formal is extremely unclear. *What* entity
146 -- should be passed? For the object declaration case we may guess that
147 -- this is the object being declared, but what about the allocator case?
149 -- Is_Limited_Ancestor_Expansion indicates that the function has been
150 -- called recursively to expand the limited ancestor to avoid copying it.
152 function Has_Mutable_Components (Typ : Entity_Id) return Boolean;
153 -- Return true if one of the component is of a discriminated type with
154 -- defaults. An aggregate for a type with mutable components must be
155 -- expanded into individual assignments.
157 procedure Initialize_Discriminants (N : Node_Id; Typ : Entity_Id);
158 -- If the type of the aggregate is a type extension with renamed discrimi-
159 -- nants, we must initialize the hidden discriminants of the parent.
160 -- Otherwise, the target object must not be initialized. The discriminants
161 -- are initialized by calling the initialization procedure for the type.
162 -- This is incorrect if the initialization of other components has any
163 -- side effects. We restrict this call to the case where the parent type
164 -- has a variant part, because this is the only case where the hidden
165 -- discriminants are accessed, namely when calling discriminant checking
166 -- functions of the parent type, and when applying a stream attribute to
167 -- an object of the derived type.
169 -----------------------------------------------------
170 -- Local Subprograms for Array Aggregate Expansion --
171 -----------------------------------------------------
173 function Aggr_Size_OK (N : Node_Id; Typ : Entity_Id) return Boolean;
174 -- Very large static aggregates present problems to the back-end, and
175 -- are transformed into assignments and loops. This function verifies
176 -- that the total number of components of an aggregate is acceptable
177 -- for transformation into a purely positional static form. It is called
178 -- prior to calling Flatten.
179 -- This function also detects and warns about one-component aggregates
180 -- that appear in a non-static context. Even if the component value is
181 -- static, such an aggregate must be expanded into an assignment.
183 procedure Convert_Array_Aggr_In_Allocator
184 (Decl : Node_Id;
185 Aggr : Node_Id;
186 Target : Node_Id);
187 -- If the aggregate appears within an allocator and can be expanded in
188 -- place, this routine generates the individual assignments to components
189 -- of the designated object. This is an optimization over the general
190 -- case, where a temporary is first created on the stack and then used to
191 -- construct the allocated object on the heap.
193 procedure Convert_To_Positional
194 (N : Node_Id;
195 Max_Others_Replicate : Nat := 5;
196 Handle_Bit_Packed : Boolean := False);
197 -- If possible, convert named notation to positional notation. This
198 -- conversion is possible only in some static cases. If the conversion is
199 -- possible, then N is rewritten with the analyzed converted aggregate.
200 -- The parameter Max_Others_Replicate controls the maximum number of
201 -- values corresponding to an others choice that will be converted to
202 -- positional notation (the default of 5 is the normal limit, and reflects
203 -- the fact that normally the loop is better than a lot of separate
204 -- assignments). Note that this limit gets overridden in any case if
205 -- either of the restrictions No_Elaboration_Code or No_Implicit_Loops is
206 -- set. The parameter Handle_Bit_Packed is usually set False (since we do
207 -- not expect the back end to handle bit packed arrays, so the normal case
208 -- of conversion is pointless), but in the special case of a call from
209 -- Packed_Array_Aggregate_Handled, we set this parameter to True, since
210 -- these are cases we handle in there.
212 procedure Expand_Array_Aggregate (N : Node_Id);
213 -- This is the top-level routine to perform array aggregate expansion.
214 -- N is the N_Aggregate node to be expanded.
216 function Backend_Processing_Possible (N : Node_Id) return Boolean;
217 -- This function checks if array aggregate N can be processed directly
218 -- by Gigi. If this is the case True is returned.
220 function Build_Array_Aggr_Code
221 (N : Node_Id;
222 Ctype : Entity_Id;
223 Index : Node_Id;
224 Into : Node_Id;
225 Scalar_Comp : Boolean;
226 Indices : List_Id := No_List;
227 Flist : Node_Id := Empty) return List_Id;
228 -- This recursive routine returns a list of statements containing the
229 -- loops and assignments that are needed for the expansion of the array
230 -- aggregate N.
232 -- N is the (sub-)aggregate node to be expanded into code. This node
233 -- has been fully analyzed, and its Etype is properly set.
235 -- Index is the index node corresponding to the array sub-aggregate N.
237 -- Into is the target expression into which we are copying the aggregate.
238 -- Note that this node may not have been analyzed yet, and so the Etype
239 -- field may not be set.
241 -- Scalar_Comp is True if the component type of the aggregate is scalar.
243 -- Indices is the current list of expressions used to index the
244 -- object we are writing into.
246 -- Flist is an expression representing the finalization list on which
247 -- to attach the controlled components if any.
249 function Number_Of_Choices (N : Node_Id) return Nat;
250 -- Returns the number of discrete choices (not including the others choice
251 -- if present) contained in (sub-)aggregate N.
253 function Late_Expansion
254 (N : Node_Id;
255 Typ : Entity_Id;
256 Target : Node_Id;
257 Flist : Node_Id := Empty;
258 Obj : Entity_Id := Empty) return List_Id;
259 -- N is a nested (record or array) aggregate that has been marked with
260 -- 'Delay_Expansion'. Typ is the expected type of the aggregate and Target
261 -- is a (duplicable) expression that will hold the result of the aggregate
262 -- expansion. Flist is the finalization list to be used to attach
263 -- controlled components. 'Obj' when non empty, carries the original
264 -- object being initialized in order to know if it needs to be attached to
265 -- the previous parameter which may not be the case in the case where
266 -- Finalize_Storage_Only is set. Basically this procedure is used to
267 -- implement top-down expansions of nested aggregates. This is necessary
268 -- for avoiding temporaries at each level as well as for propagating the
269 -- right internal finalization list.
271 function Make_OK_Assignment_Statement
272 (Sloc : Source_Ptr;
273 Name : Node_Id;
274 Expression : Node_Id) return Node_Id;
275 -- This is like Make_Assignment_Statement, except that Assignment_OK
276 -- is set in the left operand. All assignments built by this unit
277 -- use this routine. This is needed to deal with assignments to
278 -- initialized constants that are done in place.
280 function Packed_Array_Aggregate_Handled (N : Node_Id) return Boolean;
281 -- Given an array aggregate, this function handles the case of a packed
282 -- array aggregate with all constant values, where the aggregate can be
283 -- evaluated at compile time. If this is possible, then N is rewritten
284 -- to be its proper compile time value with all the components properly
285 -- assembled. The expression is analyzed and resolved and True is
286 -- returned. If this transformation is not possible, N is unchanged
287 -- and False is returned
289 function Safe_Slice_Assignment (N : Node_Id) return Boolean;
290 -- If a slice assignment has an aggregate with a single others_choice,
291 -- the assignment can be done in place even if bounds are not static,
292 -- by converting it into a loop over the discrete range of the slice.
294 ------------------
295 -- Aggr_Size_OK --
296 ------------------
298 function Aggr_Size_OK (N : Node_Id; Typ : Entity_Id) return Boolean is
299 Lo : Node_Id;
300 Hi : Node_Id;
301 Indx : Node_Id;
302 Siz : Int;
303 Lov : Uint;
304 Hiv : Uint;
306 -- The following constant determines the maximum size of an
307 -- array aggregate produced by converting named to positional
308 -- notation (e.g. from others clauses). This avoids running
309 -- away with attempts to convert huge aggregates, which hit
310 -- memory limits in the backend.
312 -- The normal limit is 5000, but we increase this limit to
313 -- 2**24 (about 16 million) if Restrictions (No_Elaboration_Code)
314 -- or Restrictions (No_Implicit_Loops) is specified, since in
315 -- either case, we are at risk of declaring the program illegal
316 -- because of this limit.
318 Max_Aggr_Size : constant Nat :=
319 5000 + (2 ** 24 - 5000) *
320 Boolean'Pos
321 (Restriction_Active (No_Elaboration_Code)
322 or else
323 Restriction_Active (No_Implicit_Loops));
325 function Component_Count (T : Entity_Id) return Int;
326 -- The limit is applied to the total number of components that the
327 -- aggregate will have, which is the number of static expressions
328 -- that will appear in the flattened array. This requires a recursive
329 -- computation of the the number of scalar components of the structure.
331 ---------------------
332 -- Component_Count --
333 ---------------------
335 function Component_Count (T : Entity_Id) return Int is
336 Res : Int := 0;
337 Comp : Entity_Id;
339 begin
340 if Is_Scalar_Type (T) then
341 return 1;
343 elsif Is_Record_Type (T) then
344 Comp := First_Component (T);
345 while Present (Comp) loop
346 Res := Res + Component_Count (Etype (Comp));
347 Next_Component (Comp);
348 end loop;
350 return Res;
352 elsif Is_Array_Type (T) then
353 declare
354 Lo : constant Node_Id :=
355 Type_Low_Bound (Etype (First_Index (T)));
356 Hi : constant Node_Id :=
357 Type_High_Bound (Etype (First_Index (T)));
359 Siz : constant Int := Component_Count (Component_Type (T));
361 begin
362 if not Compile_Time_Known_Value (Lo)
363 or else not Compile_Time_Known_Value (Hi)
364 then
365 return 0;
366 else
367 return
368 Siz * UI_To_Int (Expr_Value (Hi) - Expr_Value (Lo) + 1);
369 end if;
370 end;
372 else
373 -- Can only be a null for an access type
375 return 1;
376 end if;
377 end Component_Count;
379 -- Start of processing for Aggr_Size_OK
381 begin
382 Siz := Component_Count (Component_Type (Typ));
384 Indx := First_Index (Typ);
385 while Present (Indx) loop
386 Lo := Type_Low_Bound (Etype (Indx));
387 Hi := Type_High_Bound (Etype (Indx));
389 -- Bounds need to be known at compile time
391 if not Compile_Time_Known_Value (Lo)
392 or else not Compile_Time_Known_Value (Hi)
393 then
394 return False;
395 end if;
397 Lov := Expr_Value (Lo);
398 Hiv := Expr_Value (Hi);
400 -- A flat array is always safe
402 if Hiv < Lov then
403 return True;
404 end if;
406 -- One-component aggregates are suspicious, and if the context type
407 -- is an object declaration with non-static bounds it will trip gcc;
408 -- such an aggregate must be expanded into a single assignment.
410 if Hiv = Lov
411 and then Nkind (Parent (N)) = N_Object_Declaration
412 then
413 declare
414 Index_Type : constant Entity_Id :=
415 Etype
416 (First_Index
417 (Etype (Defining_Identifier (Parent (N)))));
418 Indx : Node_Id;
420 begin
421 if not Compile_Time_Known_Value (Type_Low_Bound (Index_Type))
422 or else not Compile_Time_Known_Value
423 (Type_High_Bound (Index_Type))
424 then
425 if Present (Component_Associations (N)) then
426 Indx :=
427 First (Choices (First (Component_Associations (N))));
428 if Is_Entity_Name (Indx)
429 and then not Is_Type (Entity (Indx))
430 then
431 Error_Msg_N
432 ("single component aggregate in non-static context?",
433 Indx);
434 Error_Msg_N ("\maybe subtype name was meant?", Indx);
435 end if;
436 end if;
438 return False;
439 end if;
440 end;
441 end if;
443 declare
444 Rng : constant Uint := Hiv - Lov + 1;
446 begin
447 -- Check if size is too large
449 if not UI_Is_In_Int_Range (Rng) then
450 return False;
451 end if;
453 Siz := Siz * UI_To_Int (Rng);
454 end;
456 if Siz <= 0
457 or else Siz > Max_Aggr_Size
458 then
459 return False;
460 end if;
462 -- Bounds must be in integer range, for later array construction
464 if not UI_Is_In_Int_Range (Lov)
465 or else
466 not UI_Is_In_Int_Range (Hiv)
467 then
468 return False;
469 end if;
471 Next_Index (Indx);
472 end loop;
474 return True;
475 end Aggr_Size_OK;
477 ---------------------------------
478 -- Backend_Processing_Possible --
479 ---------------------------------
481 -- Backend processing by Gigi/gcc is possible only if all the following
482 -- conditions are met:
484 -- 1. N is fully positional
486 -- 2. N is not a bit-packed array aggregate;
488 -- 3. The size of N's array type must be known at compile time. Note
489 -- that this implies that the component size is also known
491 -- 4. The array type of N does not follow the Fortran layout convention
492 -- or if it does it must be 1 dimensional.
494 -- 5. The array component type may not be tagged (which could necessitate
495 -- reassignment of proper tags).
497 -- 6. The array component type must not have unaligned bit components
499 -- 7. None of the components of the aggregate may be bit unaligned
500 -- components.
502 -- 8. There cannot be delayed components, since we do not know enough
503 -- at this stage to know if back end processing is possible.
505 -- 9. There cannot be any discriminated record components, since the
506 -- back end cannot handle this complex case.
508 function Backend_Processing_Possible (N : Node_Id) return Boolean is
509 Typ : constant Entity_Id := Etype (N);
510 -- Typ is the correct constrained array subtype of the aggregate
512 function Component_Check (N : Node_Id; Index : Node_Id) return Boolean;
513 -- This routine checks components of aggregate N, enforcing checks
514 -- 1, 7, 8, and 9. In the multi-dimensional case, these checks are
515 -- performed on subaggregates. The Index value is the current index
516 -- being checked in the multi-dimensional case.
518 ---------------------
519 -- Component_Check --
520 ---------------------
522 function Component_Check (N : Node_Id; Index : Node_Id) return Boolean is
523 Expr : Node_Id;
525 begin
526 -- Checks 1: (no component associations)
528 if Present (Component_Associations (N)) then
529 return False;
530 end if;
532 -- Checks on components
534 -- Recurse to check subaggregates, which may appear in qualified
535 -- expressions. If delayed, the front-end will have to expand.
536 -- If the component is a discriminated record, treat as non-static,
537 -- as the back-end cannot handle this properly.
539 Expr := First (Expressions (N));
540 while Present (Expr) loop
542 -- Checks 8: (no delayed components)
544 if Is_Delayed_Aggregate (Expr) then
545 return False;
546 end if;
548 -- Checks 9: (no discriminated records)
550 if Present (Etype (Expr))
551 and then Is_Record_Type (Etype (Expr))
552 and then Has_Discriminants (Etype (Expr))
553 then
554 return False;
555 end if;
557 -- Checks 7. Component must not be bit aligned component
559 if Possible_Bit_Aligned_Component (Expr) then
560 return False;
561 end if;
563 -- Recursion to following indexes for multiple dimension case
565 if Present (Next_Index (Index))
566 and then not Component_Check (Expr, Next_Index (Index))
567 then
568 return False;
569 end if;
571 -- All checks for that component finished, on to next
573 Next (Expr);
574 end loop;
576 return True;
577 end Component_Check;
579 -- Start of processing for Backend_Processing_Possible
581 begin
582 -- Checks 2 (array must not be bit packed)
584 if Is_Bit_Packed_Array (Typ) then
585 return False;
586 end if;
588 -- If component is limited, aggregate must be expanded because each
589 -- component assignment must be built in place.
591 if Is_Inherently_Limited_Type (Component_Type (Typ)) then
592 return False;
593 end if;
595 -- Checks 4 (array must not be multi-dimensional Fortran case)
597 if Convention (Typ) = Convention_Fortran
598 and then Number_Dimensions (Typ) > 1
599 then
600 return False;
601 end if;
603 -- Checks 3 (size of array must be known at compile time)
605 if not Size_Known_At_Compile_Time (Typ) then
606 return False;
607 end if;
609 -- Checks on components
611 if not Component_Check (N, First_Index (Typ)) then
612 return False;
613 end if;
615 -- Checks 5 (if the component type is tagged, then we may need to do
616 -- tag adjustments. Perhaps this should be refined to check for any
617 -- component associations that actually need tag adjustment, similar
618 -- to the test in Component_Not_OK_For_Backend for record aggregates
619 -- with tagged components, but not clear whether it's worthwhile ???;
620 -- in the case of the JVM, object tags are handled implicitly)
622 if Is_Tagged_Type (Component_Type (Typ)) and then VM_Target = No_VM then
623 return False;
624 end if;
626 -- Checks 6 (component type must not have bit aligned components)
628 if Type_May_Have_Bit_Aligned_Components (Component_Type (Typ)) then
629 return False;
630 end if;
632 -- Backend processing is possible
634 Set_Size_Known_At_Compile_Time (Etype (N), True);
635 return True;
636 end Backend_Processing_Possible;
638 ---------------------------
639 -- Build_Array_Aggr_Code --
640 ---------------------------
642 -- The code that we generate from a one dimensional aggregate is
644 -- 1. If the sub-aggregate contains discrete choices we
646 -- (a) Sort the discrete choices
648 -- (b) Otherwise for each discrete choice that specifies a range we
649 -- emit a loop. If a range specifies a maximum of three values, or
650 -- we are dealing with an expression we emit a sequence of
651 -- assignments instead of a loop.
653 -- (c) Generate the remaining loops to cover the others choice if any
655 -- 2. If the aggregate contains positional elements we
657 -- (a) translate the positional elements in a series of assignments
659 -- (b) Generate a final loop to cover the others choice if any.
660 -- Note that this final loop has to be a while loop since the case
662 -- L : Integer := Integer'Last;
663 -- H : Integer := Integer'Last;
664 -- A : array (L .. H) := (1, others =>0);
666 -- cannot be handled by a for loop. Thus for the following
668 -- array (L .. H) := (.. positional elements.., others =>E);
670 -- we always generate something like:
672 -- J : Index_Type := Index_Of_Last_Positional_Element;
673 -- while J < H loop
674 -- J := Index_Base'Succ (J)
675 -- Tmp (J) := E;
676 -- end loop;
678 function Build_Array_Aggr_Code
679 (N : Node_Id;
680 Ctype : Entity_Id;
681 Index : Node_Id;
682 Into : Node_Id;
683 Scalar_Comp : Boolean;
684 Indices : List_Id := No_List;
685 Flist : Node_Id := Empty) return List_Id
687 Loc : constant Source_Ptr := Sloc (N);
688 Index_Base : constant Entity_Id := Base_Type (Etype (Index));
689 Index_Base_L : constant Node_Id := Type_Low_Bound (Index_Base);
690 Index_Base_H : constant Node_Id := Type_High_Bound (Index_Base);
692 function Add (Val : Int; To : Node_Id) return Node_Id;
693 -- Returns an expression where Val is added to expression To, unless
694 -- To+Val is provably out of To's base type range. To must be an
695 -- already analyzed expression.
697 function Empty_Range (L, H : Node_Id) return Boolean;
698 -- Returns True if the range defined by L .. H is certainly empty
700 function Equal (L, H : Node_Id) return Boolean;
701 -- Returns True if L = H for sure
703 function Index_Base_Name return Node_Id;
704 -- Returns a new reference to the index type name
706 function Gen_Assign (Ind : Node_Id; Expr : Node_Id) return List_Id;
707 -- Ind must be a side-effect free expression. If the input aggregate
708 -- N to Build_Loop contains no sub-aggregates, then this function
709 -- returns the assignment statement:
711 -- Into (Indices, Ind) := Expr;
713 -- Otherwise we call Build_Code recursively
715 -- Ada 2005 (AI-287): In case of default initialized component, Expr
716 -- is empty and we generate a call to the corresponding IP subprogram.
718 function Gen_Loop (L, H : Node_Id; Expr : Node_Id) return List_Id;
719 -- Nodes L and H must be side-effect free expressions.
720 -- If the input aggregate N to Build_Loop contains no sub-aggregates,
721 -- This routine returns the for loop statement
723 -- for J in Index_Base'(L) .. Index_Base'(H) loop
724 -- Into (Indices, J) := Expr;
725 -- end loop;
727 -- Otherwise we call Build_Code recursively.
728 -- As an optimization if the loop covers 3 or less scalar elements we
729 -- generate a sequence of assignments.
731 function Gen_While (L, H : Node_Id; Expr : Node_Id) return List_Id;
732 -- Nodes L and H must be side-effect free expressions.
733 -- If the input aggregate N to Build_Loop contains no sub-aggregates,
734 -- This routine returns the while loop statement
736 -- J : Index_Base := L;
737 -- while J < H loop
738 -- J := Index_Base'Succ (J);
739 -- Into (Indices, J) := Expr;
740 -- end loop;
742 -- Otherwise we call Build_Code recursively
744 function Local_Compile_Time_Known_Value (E : Node_Id) return Boolean;
745 function Local_Expr_Value (E : Node_Id) return Uint;
746 -- These two Local routines are used to replace the corresponding ones
747 -- in sem_eval because while processing the bounds of an aggregate with
748 -- discrete choices whose index type is an enumeration, we build static
749 -- expressions not recognized by Compile_Time_Known_Value as such since
750 -- they have not yet been analyzed and resolved. All the expressions in
751 -- question are things like Index_Base_Name'Val (Const) which we can
752 -- easily recognize as being constant.
754 ---------
755 -- Add --
756 ---------
758 function Add (Val : Int; To : Node_Id) return Node_Id is
759 Expr_Pos : Node_Id;
760 Expr : Node_Id;
761 To_Pos : Node_Id;
762 U_To : Uint;
763 U_Val : constant Uint := UI_From_Int (Val);
765 begin
766 -- Note: do not try to optimize the case of Val = 0, because
767 -- we need to build a new node with the proper Sloc value anyway.
769 -- First test if we can do constant folding
771 if Local_Compile_Time_Known_Value (To) then
772 U_To := Local_Expr_Value (To) + Val;
774 -- Determine if our constant is outside the range of the index.
775 -- If so return an Empty node. This empty node will be caught
776 -- by Empty_Range below.
778 if Compile_Time_Known_Value (Index_Base_L)
779 and then U_To < Expr_Value (Index_Base_L)
780 then
781 return Empty;
783 elsif Compile_Time_Known_Value (Index_Base_H)
784 and then U_To > Expr_Value (Index_Base_H)
785 then
786 return Empty;
787 end if;
789 Expr_Pos := Make_Integer_Literal (Loc, U_To);
790 Set_Is_Static_Expression (Expr_Pos);
792 if not Is_Enumeration_Type (Index_Base) then
793 Expr := Expr_Pos;
795 -- If we are dealing with enumeration return
796 -- Index_Base'Val (Expr_Pos)
798 else
799 Expr :=
800 Make_Attribute_Reference
801 (Loc,
802 Prefix => Index_Base_Name,
803 Attribute_Name => Name_Val,
804 Expressions => New_List (Expr_Pos));
805 end if;
807 return Expr;
808 end if;
810 -- If we are here no constant folding possible
812 if not Is_Enumeration_Type (Index_Base) then
813 Expr :=
814 Make_Op_Add (Loc,
815 Left_Opnd => Duplicate_Subexpr (To),
816 Right_Opnd => Make_Integer_Literal (Loc, U_Val));
818 -- If we are dealing with enumeration return
819 -- Index_Base'Val (Index_Base'Pos (To) + Val)
821 else
822 To_Pos :=
823 Make_Attribute_Reference
824 (Loc,
825 Prefix => Index_Base_Name,
826 Attribute_Name => Name_Pos,
827 Expressions => New_List (Duplicate_Subexpr (To)));
829 Expr_Pos :=
830 Make_Op_Add (Loc,
831 Left_Opnd => To_Pos,
832 Right_Opnd => Make_Integer_Literal (Loc, U_Val));
834 Expr :=
835 Make_Attribute_Reference
836 (Loc,
837 Prefix => Index_Base_Name,
838 Attribute_Name => Name_Val,
839 Expressions => New_List (Expr_Pos));
840 end if;
842 return Expr;
843 end Add;
845 -----------------
846 -- Empty_Range --
847 -----------------
849 function Empty_Range (L, H : Node_Id) return Boolean is
850 Is_Empty : Boolean := False;
851 Low : Node_Id;
852 High : Node_Id;
854 begin
855 -- First check if L or H were already detected as overflowing the
856 -- index base range type by function Add above. If this is so Add
857 -- returns the empty node.
859 if No (L) or else No (H) then
860 return True;
861 end if;
863 for J in 1 .. 3 loop
864 case J is
866 -- L > H range is empty
868 when 1 =>
869 Low := L;
870 High := H;
872 -- B_L > H range must be empty
874 when 2 =>
875 Low := Index_Base_L;
876 High := H;
878 -- L > B_H range must be empty
880 when 3 =>
881 Low := L;
882 High := Index_Base_H;
883 end case;
885 if Local_Compile_Time_Known_Value (Low)
886 and then Local_Compile_Time_Known_Value (High)
887 then
888 Is_Empty :=
889 UI_Gt (Local_Expr_Value (Low), Local_Expr_Value (High));
890 end if;
892 exit when Is_Empty;
893 end loop;
895 return Is_Empty;
896 end Empty_Range;
898 -----------
899 -- Equal --
900 -----------
902 function Equal (L, H : Node_Id) return Boolean is
903 begin
904 if L = H then
905 return True;
907 elsif Local_Compile_Time_Known_Value (L)
908 and then Local_Compile_Time_Known_Value (H)
909 then
910 return UI_Eq (Local_Expr_Value (L), Local_Expr_Value (H));
911 end if;
913 return False;
914 end Equal;
916 ----------------
917 -- Gen_Assign --
918 ----------------
920 function Gen_Assign (Ind : Node_Id; Expr : Node_Id) return List_Id is
921 L : constant List_Id := New_List;
922 F : Entity_Id;
923 A : Node_Id;
925 New_Indices : List_Id;
926 Indexed_Comp : Node_Id;
927 Expr_Q : Node_Id;
928 Comp_Type : Entity_Id := Empty;
930 function Add_Loop_Actions (Lis : List_Id) return List_Id;
931 -- Collect insert_actions generated in the construction of a
932 -- loop, and prepend them to the sequence of assignments to
933 -- complete the eventual body of the loop.
935 ----------------------
936 -- Add_Loop_Actions --
937 ----------------------
939 function Add_Loop_Actions (Lis : List_Id) return List_Id is
940 Res : List_Id;
942 begin
943 -- Ada 2005 (AI-287): Do nothing else in case of default
944 -- initialized component.
946 if No (Expr) then
947 return Lis;
949 elsif Nkind (Parent (Expr)) = N_Component_Association
950 and then Present (Loop_Actions (Parent (Expr)))
951 then
952 Append_List (Lis, Loop_Actions (Parent (Expr)));
953 Res := Loop_Actions (Parent (Expr));
954 Set_Loop_Actions (Parent (Expr), No_List);
955 return Res;
957 else
958 return Lis;
959 end if;
960 end Add_Loop_Actions;
962 -- Start of processing for Gen_Assign
964 begin
965 if No (Indices) then
966 New_Indices := New_List;
967 else
968 New_Indices := New_Copy_List_Tree (Indices);
969 end if;
971 Append_To (New_Indices, Ind);
973 if Present (Flist) then
974 F := New_Copy_Tree (Flist);
976 elsif Present (Etype (N)) and then Needs_Finalization (Etype (N)) then
977 if Is_Entity_Name (Into)
978 and then Present (Scope (Entity (Into)))
979 then
980 F := Find_Final_List (Scope (Entity (Into)));
981 else
982 F := Find_Final_List (Current_Scope);
983 end if;
984 else
985 F := Empty;
986 end if;
988 if Present (Next_Index (Index)) then
989 return
990 Add_Loop_Actions (
991 Build_Array_Aggr_Code
992 (N => Expr,
993 Ctype => Ctype,
994 Index => Next_Index (Index),
995 Into => Into,
996 Scalar_Comp => Scalar_Comp,
997 Indices => New_Indices,
998 Flist => F));
999 end if;
1001 -- If we get here then we are at a bottom-level (sub-)aggregate
1003 Indexed_Comp :=
1004 Checks_Off
1005 (Make_Indexed_Component (Loc,
1006 Prefix => New_Copy_Tree (Into),
1007 Expressions => New_Indices));
1009 Set_Assignment_OK (Indexed_Comp);
1011 -- Ada 2005 (AI-287): In case of default initialized component, Expr
1012 -- is not present (and therefore we also initialize Expr_Q to empty).
1014 if No (Expr) then
1015 Expr_Q := Empty;
1016 elsif Nkind (Expr) = N_Qualified_Expression then
1017 Expr_Q := Expression (Expr);
1018 else
1019 Expr_Q := Expr;
1020 end if;
1022 if Present (Etype (N))
1023 and then Etype (N) /= Any_Composite
1024 then
1025 Comp_Type := Component_Type (Etype (N));
1026 pragma Assert (Comp_Type = Ctype); -- AI-287
1028 elsif Present (Next (First (New_Indices))) then
1030 -- Ada 2005 (AI-287): Do nothing in case of default initialized
1031 -- component because we have received the component type in
1032 -- the formal parameter Ctype.
1034 -- ??? Some assert pragmas have been added to check if this new
1035 -- formal can be used to replace this code in all cases.
1037 if Present (Expr) then
1039 -- This is a multidimensional array. Recover the component
1040 -- type from the outermost aggregate, because subaggregates
1041 -- do not have an assigned type.
1043 declare
1044 P : Node_Id;
1046 begin
1047 P := Parent (Expr);
1048 while Present (P) loop
1049 if Nkind (P) = N_Aggregate
1050 and then Present (Etype (P))
1051 then
1052 Comp_Type := Component_Type (Etype (P));
1053 exit;
1055 else
1056 P := Parent (P);
1057 end if;
1058 end loop;
1060 pragma Assert (Comp_Type = Ctype); -- AI-287
1061 end;
1062 end if;
1063 end if;
1065 -- Ada 2005 (AI-287): We only analyze the expression in case of non-
1066 -- default initialized components (otherwise Expr_Q is not present).
1068 if Present (Expr_Q)
1069 and then (Nkind (Expr_Q) = N_Aggregate
1070 or else Nkind (Expr_Q) = N_Extension_Aggregate)
1071 then
1072 -- At this stage the Expression may not have been
1073 -- analyzed yet because the array aggregate code has not
1074 -- been updated to use the Expansion_Delayed flag and
1075 -- avoid analysis altogether to solve the same problem
1076 -- (see Resolve_Aggr_Expr). So let us do the analysis of
1077 -- non-array aggregates now in order to get the value of
1078 -- Expansion_Delayed flag for the inner aggregate ???
1080 if Present (Comp_Type) and then not Is_Array_Type (Comp_Type) then
1081 Analyze_And_Resolve (Expr_Q, Comp_Type);
1082 end if;
1084 if Is_Delayed_Aggregate (Expr_Q) then
1086 -- This is either a subaggregate of a multidimentional array,
1087 -- or a component of an array type whose component type is
1088 -- also an array. In the latter case, the expression may have
1089 -- component associations that provide different bounds from
1090 -- those of the component type, and sliding must occur. Instead
1091 -- of decomposing the current aggregate assignment, force the
1092 -- re-analysis of the assignment, so that a temporary will be
1093 -- generated in the usual fashion, and sliding will take place.
1095 if Nkind (Parent (N)) = N_Assignment_Statement
1096 and then Is_Array_Type (Comp_Type)
1097 and then Present (Component_Associations (Expr_Q))
1098 and then Must_Slide (Comp_Type, Etype (Expr_Q))
1099 then
1100 Set_Expansion_Delayed (Expr_Q, False);
1101 Set_Analyzed (Expr_Q, False);
1103 else
1104 return
1105 Add_Loop_Actions (
1106 Late_Expansion (
1107 Expr_Q, Etype (Expr_Q), Indexed_Comp, F));
1108 end if;
1109 end if;
1110 end if;
1112 -- Ada 2005 (AI-287): In case of default initialized component, call
1113 -- the initialization subprogram associated with the component type.
1114 -- If the component type is an access type, add an explicit null
1115 -- assignment, because for the back-end there is an initialization
1116 -- present for the whole aggregate, and no default initialization
1117 -- will take place.
1119 -- In addition, if the component type is controlled, we must call
1120 -- its Initialize procedure explicitly, because there is no explicit
1121 -- object creation that will invoke it otherwise.
1123 if No (Expr) then
1124 if Present (Base_Init_Proc (Base_Type (Ctype)))
1125 or else Has_Task (Base_Type (Ctype))
1126 then
1127 Append_List_To (L,
1128 Build_Initialization_Call (Loc,
1129 Id_Ref => Indexed_Comp,
1130 Typ => Ctype,
1131 With_Default_Init => True));
1133 elsif Is_Access_Type (Ctype) then
1134 Append_To (L,
1135 Make_Assignment_Statement (Loc,
1136 Name => Indexed_Comp,
1137 Expression => Make_Null (Loc)));
1138 end if;
1140 if Needs_Finalization (Ctype) then
1141 Append_List_To (L,
1142 Make_Init_Call (
1143 Ref => New_Copy_Tree (Indexed_Comp),
1144 Typ => Ctype,
1145 Flist_Ref => Find_Final_List (Current_Scope),
1146 With_Attach => Make_Integer_Literal (Loc, 1)));
1147 end if;
1149 else
1150 -- Now generate the assignment with no associated controlled
1151 -- actions since the target of the assignment may not have been
1152 -- initialized, it is not possible to Finalize it as expected by
1153 -- normal controlled assignment. The rest of the controlled
1154 -- actions are done manually with the proper finalization list
1155 -- coming from the context.
1157 A :=
1158 Make_OK_Assignment_Statement (Loc,
1159 Name => Indexed_Comp,
1160 Expression => New_Copy_Tree (Expr));
1162 if Present (Comp_Type) and then Needs_Finalization (Comp_Type) then
1163 Set_No_Ctrl_Actions (A);
1165 -- If this is an aggregate for an array of arrays, each
1166 -- sub-aggregate will be expanded as well, and even with
1167 -- No_Ctrl_Actions the assignments of inner components will
1168 -- require attachment in their assignments to temporaries.
1169 -- These temporaries must be finalized for each subaggregate,
1170 -- to prevent multiple attachments of the same temporary
1171 -- location to same finalization chain (and consequently
1172 -- circular lists). To ensure that finalization takes place
1173 -- for each subaggregate we wrap the assignment in a block.
1175 if Is_Array_Type (Comp_Type)
1176 and then Nkind (Expr) = N_Aggregate
1177 then
1178 A :=
1179 Make_Block_Statement (Loc,
1180 Handled_Statement_Sequence =>
1181 Make_Handled_Sequence_Of_Statements (Loc,
1182 Statements => New_List (A)));
1183 end if;
1184 end if;
1186 Append_To (L, A);
1188 -- Adjust the tag if tagged (because of possible view
1189 -- conversions), unless compiling for the Java VM where
1190 -- tags are implicit.
1192 if Present (Comp_Type)
1193 and then Is_Tagged_Type (Comp_Type)
1194 and then VM_Target = No_VM
1195 then
1196 A :=
1197 Make_OK_Assignment_Statement (Loc,
1198 Name =>
1199 Make_Selected_Component (Loc,
1200 Prefix => New_Copy_Tree (Indexed_Comp),
1201 Selector_Name =>
1202 New_Reference_To
1203 (First_Tag_Component (Comp_Type), Loc)),
1205 Expression =>
1206 Unchecked_Convert_To (RTE (RE_Tag),
1207 New_Reference_To
1208 (Node (First_Elmt (Access_Disp_Table (Comp_Type))),
1209 Loc)));
1211 Append_To (L, A);
1212 end if;
1214 -- Adjust and attach the component to the proper final list, which
1215 -- can be the controller of the outer record object or the final
1216 -- list associated with the scope.
1218 -- If the component is itself an array of controlled types, whose
1219 -- value is given by a sub-aggregate, then the attach calls have
1220 -- been generated when individual subcomponent are assigned, and
1221 -- must not be done again to prevent malformed finalization chains
1222 -- (see comments above, concerning the creation of a block to hold
1223 -- inner finalization actions).
1225 if Present (Comp_Type)
1226 and then Needs_Finalization (Comp_Type)
1227 and then not Is_Limited_Type (Comp_Type)
1228 and then
1229 (not Is_Array_Type (Comp_Type)
1230 or else not Is_Controlled (Component_Type (Comp_Type))
1231 or else Nkind (Expr) /= N_Aggregate)
1232 then
1233 Append_List_To (L,
1234 Make_Adjust_Call (
1235 Ref => New_Copy_Tree (Indexed_Comp),
1236 Typ => Comp_Type,
1237 Flist_Ref => F,
1238 With_Attach => Make_Integer_Literal (Loc, 1)));
1239 end if;
1240 end if;
1242 return Add_Loop_Actions (L);
1243 end Gen_Assign;
1245 --------------
1246 -- Gen_Loop --
1247 --------------
1249 function Gen_Loop (L, H : Node_Id; Expr : Node_Id) return List_Id is
1250 L_J : Node_Id;
1252 L_Range : Node_Id;
1253 -- Index_Base'(L) .. Index_Base'(H)
1255 L_Iteration_Scheme : Node_Id;
1256 -- L_J in Index_Base'(L) .. Index_Base'(H)
1258 L_Body : List_Id;
1259 -- The statements to execute in the loop
1261 S : constant List_Id := New_List;
1262 -- List of statements
1264 Tcopy : Node_Id;
1265 -- Copy of expression tree, used for checking purposes
1267 begin
1268 -- If loop bounds define an empty range return the null statement
1270 if Empty_Range (L, H) then
1271 Append_To (S, Make_Null_Statement (Loc));
1273 -- Ada 2005 (AI-287): Nothing else need to be done in case of
1274 -- default initialized component.
1276 if No (Expr) then
1277 null;
1279 else
1280 -- The expression must be type-checked even though no component
1281 -- of the aggregate will have this value. This is done only for
1282 -- actual components of the array, not for subaggregates. Do
1283 -- the check on a copy, because the expression may be shared
1284 -- among several choices, some of which might be non-null.
1286 if Present (Etype (N))
1287 and then Is_Array_Type (Etype (N))
1288 and then No (Next_Index (Index))
1289 then
1290 Expander_Mode_Save_And_Set (False);
1291 Tcopy := New_Copy_Tree (Expr);
1292 Set_Parent (Tcopy, N);
1293 Analyze_And_Resolve (Tcopy, Component_Type (Etype (N)));
1294 Expander_Mode_Restore;
1295 end if;
1296 end if;
1298 return S;
1300 -- If loop bounds are the same then generate an assignment
1302 elsif Equal (L, H) then
1303 return Gen_Assign (New_Copy_Tree (L), Expr);
1305 -- If H - L <= 2 then generate a sequence of assignments when we are
1306 -- processing the bottom most aggregate and it contains scalar
1307 -- components.
1309 elsif No (Next_Index (Index))
1310 and then Scalar_Comp
1311 and then Local_Compile_Time_Known_Value (L)
1312 and then Local_Compile_Time_Known_Value (H)
1313 and then Local_Expr_Value (H) - Local_Expr_Value (L) <= 2
1314 then
1316 Append_List_To (S, Gen_Assign (New_Copy_Tree (L), Expr));
1317 Append_List_To (S, Gen_Assign (Add (1, To => L), Expr));
1319 if Local_Expr_Value (H) - Local_Expr_Value (L) = 2 then
1320 Append_List_To (S, Gen_Assign (Add (2, To => L), Expr));
1321 end if;
1323 return S;
1324 end if;
1326 -- Otherwise construct the loop, starting with the loop index L_J
1328 L_J := Make_Defining_Identifier (Loc, New_Internal_Name ('J'));
1330 -- Construct "L .. H"
1332 L_Range :=
1333 Make_Range
1334 (Loc,
1335 Low_Bound => Make_Qualified_Expression
1336 (Loc,
1337 Subtype_Mark => Index_Base_Name,
1338 Expression => L),
1339 High_Bound => Make_Qualified_Expression
1340 (Loc,
1341 Subtype_Mark => Index_Base_Name,
1342 Expression => H));
1344 -- Construct "for L_J in Index_Base range L .. H"
1346 L_Iteration_Scheme :=
1347 Make_Iteration_Scheme
1348 (Loc,
1349 Loop_Parameter_Specification =>
1350 Make_Loop_Parameter_Specification
1351 (Loc,
1352 Defining_Identifier => L_J,
1353 Discrete_Subtype_Definition => L_Range));
1355 -- Construct the statements to execute in the loop body
1357 L_Body := Gen_Assign (New_Reference_To (L_J, Loc), Expr);
1359 -- Construct the final loop
1361 Append_To (S, Make_Implicit_Loop_Statement
1362 (Node => N,
1363 Identifier => Empty,
1364 Iteration_Scheme => L_Iteration_Scheme,
1365 Statements => L_Body));
1367 -- A small optimization: if the aggregate is initialized with a box
1368 -- and the component type has no initialization procedure, remove the
1369 -- useless empty loop.
1371 if Nkind (First (S)) = N_Loop_Statement
1372 and then Is_Empty_List (Statements (First (S)))
1373 then
1374 return New_List (Make_Null_Statement (Loc));
1375 else
1376 return S;
1377 end if;
1378 end Gen_Loop;
1380 ---------------
1381 -- Gen_While --
1382 ---------------
1384 -- The code built is
1386 -- W_J : Index_Base := L;
1387 -- while W_J < H loop
1388 -- W_J := Index_Base'Succ (W);
1389 -- L_Body;
1390 -- end loop;
1392 function Gen_While (L, H : Node_Id; Expr : Node_Id) return List_Id is
1393 W_J : Node_Id;
1395 W_Decl : Node_Id;
1396 -- W_J : Base_Type := L;
1398 W_Iteration_Scheme : Node_Id;
1399 -- while W_J < H
1401 W_Index_Succ : Node_Id;
1402 -- Index_Base'Succ (J)
1404 W_Increment : Node_Id;
1405 -- W_J := Index_Base'Succ (W)
1407 W_Body : constant List_Id := New_List;
1408 -- The statements to execute in the loop
1410 S : constant List_Id := New_List;
1411 -- list of statement
1413 begin
1414 -- If loop bounds define an empty range or are equal return null
1416 if Empty_Range (L, H) or else Equal (L, H) then
1417 Append_To (S, Make_Null_Statement (Loc));
1418 return S;
1419 end if;
1421 -- Build the decl of W_J
1423 W_J := Make_Defining_Identifier (Loc, New_Internal_Name ('J'));
1424 W_Decl :=
1425 Make_Object_Declaration
1426 (Loc,
1427 Defining_Identifier => W_J,
1428 Object_Definition => Index_Base_Name,
1429 Expression => L);
1431 -- Theoretically we should do a New_Copy_Tree (L) here, but we know
1432 -- that in this particular case L is a fresh Expr generated by
1433 -- Add which we are the only ones to use.
1435 Append_To (S, W_Decl);
1437 -- Construct " while W_J < H"
1439 W_Iteration_Scheme :=
1440 Make_Iteration_Scheme
1441 (Loc,
1442 Condition => Make_Op_Lt
1443 (Loc,
1444 Left_Opnd => New_Reference_To (W_J, Loc),
1445 Right_Opnd => New_Copy_Tree (H)));
1447 -- Construct the statements to execute in the loop body
1449 W_Index_Succ :=
1450 Make_Attribute_Reference
1451 (Loc,
1452 Prefix => Index_Base_Name,
1453 Attribute_Name => Name_Succ,
1454 Expressions => New_List (New_Reference_To (W_J, Loc)));
1456 W_Increment :=
1457 Make_OK_Assignment_Statement
1458 (Loc,
1459 Name => New_Reference_To (W_J, Loc),
1460 Expression => W_Index_Succ);
1462 Append_To (W_Body, W_Increment);
1463 Append_List_To (W_Body,
1464 Gen_Assign (New_Reference_To (W_J, Loc), Expr));
1466 -- Construct the final loop
1468 Append_To (S, Make_Implicit_Loop_Statement
1469 (Node => N,
1470 Identifier => Empty,
1471 Iteration_Scheme => W_Iteration_Scheme,
1472 Statements => W_Body));
1474 return S;
1475 end Gen_While;
1477 ---------------------
1478 -- Index_Base_Name --
1479 ---------------------
1481 function Index_Base_Name return Node_Id is
1482 begin
1483 return New_Reference_To (Index_Base, Sloc (N));
1484 end Index_Base_Name;
1486 ------------------------------------
1487 -- Local_Compile_Time_Known_Value --
1488 ------------------------------------
1490 function Local_Compile_Time_Known_Value (E : Node_Id) return Boolean is
1491 begin
1492 return Compile_Time_Known_Value (E)
1493 or else
1494 (Nkind (E) = N_Attribute_Reference
1495 and then Attribute_Name (E) = Name_Val
1496 and then Compile_Time_Known_Value (First (Expressions (E))));
1497 end Local_Compile_Time_Known_Value;
1499 ----------------------
1500 -- Local_Expr_Value --
1501 ----------------------
1503 function Local_Expr_Value (E : Node_Id) return Uint is
1504 begin
1505 if Compile_Time_Known_Value (E) then
1506 return Expr_Value (E);
1507 else
1508 return Expr_Value (First (Expressions (E)));
1509 end if;
1510 end Local_Expr_Value;
1512 -- Build_Array_Aggr_Code Variables
1514 Assoc : Node_Id;
1515 Choice : Node_Id;
1516 Expr : Node_Id;
1517 Typ : Entity_Id;
1519 Others_Expr : Node_Id := Empty;
1520 Others_Box_Present : Boolean := False;
1522 Aggr_L : constant Node_Id := Low_Bound (Aggregate_Bounds (N));
1523 Aggr_H : constant Node_Id := High_Bound (Aggregate_Bounds (N));
1524 -- The aggregate bounds of this specific sub-aggregate. Note that if
1525 -- the code generated by Build_Array_Aggr_Code is executed then these
1526 -- bounds are OK. Otherwise a Constraint_Error would have been raised.
1528 Aggr_Low : constant Node_Id := Duplicate_Subexpr_No_Checks (Aggr_L);
1529 Aggr_High : constant Node_Id := Duplicate_Subexpr_No_Checks (Aggr_H);
1530 -- After Duplicate_Subexpr these are side-effect free
1532 Low : Node_Id;
1533 High : Node_Id;
1535 Nb_Choices : Nat := 0;
1536 Table : Case_Table_Type (1 .. Number_Of_Choices (N));
1537 -- Used to sort all the different choice values
1539 Nb_Elements : Int;
1540 -- Number of elements in the positional aggregate
1542 New_Code : constant List_Id := New_List;
1544 -- Start of processing for Build_Array_Aggr_Code
1546 begin
1547 -- First before we start, a special case. if we have a bit packed
1548 -- array represented as a modular type, then clear the value to
1549 -- zero first, to ensure that unused bits are properly cleared.
1551 Typ := Etype (N);
1553 if Present (Typ)
1554 and then Is_Bit_Packed_Array (Typ)
1555 and then Is_Modular_Integer_Type (Packed_Array_Type (Typ))
1556 then
1557 Append_To (New_Code,
1558 Make_Assignment_Statement (Loc,
1559 Name => New_Copy_Tree (Into),
1560 Expression =>
1561 Unchecked_Convert_To (Typ,
1562 Make_Integer_Literal (Loc, Uint_0))));
1563 end if;
1565 -- If the component type contains tasks, we need to build a Master
1566 -- entity in the current scope, because it will be needed if build-
1567 -- in-place functions are called in the expanded code.
1569 if Nkind (Parent (N)) = N_Object_Declaration
1570 and then Has_Task (Typ)
1571 then
1572 Build_Master_Entity (Defining_Identifier (Parent (N)));
1573 end if;
1575 -- STEP 1: Process component associations
1577 -- For those associations that may generate a loop, initialize
1578 -- Loop_Actions to collect inserted actions that may be crated.
1580 -- Skip this if no component associations
1582 if No (Expressions (N)) then
1584 -- STEP 1 (a): Sort the discrete choices
1586 Assoc := First (Component_Associations (N));
1587 while Present (Assoc) loop
1588 Choice := First (Choices (Assoc));
1589 while Present (Choice) loop
1590 if Nkind (Choice) = N_Others_Choice then
1591 Set_Loop_Actions (Assoc, New_List);
1593 if Box_Present (Assoc) then
1594 Others_Box_Present := True;
1595 else
1596 Others_Expr := Expression (Assoc);
1597 end if;
1598 exit;
1599 end if;
1601 Get_Index_Bounds (Choice, Low, High);
1603 if Low /= High then
1604 Set_Loop_Actions (Assoc, New_List);
1605 end if;
1607 Nb_Choices := Nb_Choices + 1;
1608 if Box_Present (Assoc) then
1609 Table (Nb_Choices) := (Choice_Lo => Low,
1610 Choice_Hi => High,
1611 Choice_Node => Empty);
1612 else
1613 Table (Nb_Choices) := (Choice_Lo => Low,
1614 Choice_Hi => High,
1615 Choice_Node => Expression (Assoc));
1616 end if;
1617 Next (Choice);
1618 end loop;
1620 Next (Assoc);
1621 end loop;
1623 -- If there is more than one set of choices these must be static
1624 -- and we can therefore sort them. Remember that Nb_Choices does not
1625 -- account for an others choice.
1627 if Nb_Choices > 1 then
1628 Sort_Case_Table (Table);
1629 end if;
1631 -- STEP 1 (b): take care of the whole set of discrete choices
1633 for J in 1 .. Nb_Choices loop
1634 Low := Table (J).Choice_Lo;
1635 High := Table (J).Choice_Hi;
1636 Expr := Table (J).Choice_Node;
1637 Append_List (Gen_Loop (Low, High, Expr), To => New_Code);
1638 end loop;
1640 -- STEP 1 (c): generate the remaining loops to cover others choice
1641 -- We don't need to generate loops over empty gaps, but if there is
1642 -- a single empty range we must analyze the expression for semantics
1644 if Present (Others_Expr) or else Others_Box_Present then
1645 declare
1646 First : Boolean := True;
1648 begin
1649 for J in 0 .. Nb_Choices loop
1650 if J = 0 then
1651 Low := Aggr_Low;
1652 else
1653 Low := Add (1, To => Table (J).Choice_Hi);
1654 end if;
1656 if J = Nb_Choices then
1657 High := Aggr_High;
1658 else
1659 High := Add (-1, To => Table (J + 1).Choice_Lo);
1660 end if;
1662 -- If this is an expansion within an init proc, make
1663 -- sure that discriminant references are replaced by
1664 -- the corresponding discriminal.
1666 if Inside_Init_Proc then
1667 if Is_Entity_Name (Low)
1668 and then Ekind (Entity (Low)) = E_Discriminant
1669 then
1670 Set_Entity (Low, Discriminal (Entity (Low)));
1671 end if;
1673 if Is_Entity_Name (High)
1674 and then Ekind (Entity (High)) = E_Discriminant
1675 then
1676 Set_Entity (High, Discriminal (Entity (High)));
1677 end if;
1678 end if;
1680 if First
1681 or else not Empty_Range (Low, High)
1682 then
1683 First := False;
1684 Append_List
1685 (Gen_Loop (Low, High, Others_Expr), To => New_Code);
1686 end if;
1687 end loop;
1688 end;
1689 end if;
1691 -- STEP 2: Process positional components
1693 else
1694 -- STEP 2 (a): Generate the assignments for each positional element
1695 -- Note that here we have to use Aggr_L rather than Aggr_Low because
1696 -- Aggr_L is analyzed and Add wants an analyzed expression.
1698 Expr := First (Expressions (N));
1699 Nb_Elements := -1;
1700 while Present (Expr) loop
1701 Nb_Elements := Nb_Elements + 1;
1702 Append_List (Gen_Assign (Add (Nb_Elements, To => Aggr_L), Expr),
1703 To => New_Code);
1704 Next (Expr);
1705 end loop;
1707 -- STEP 2 (b): Generate final loop if an others choice is present
1708 -- Here Nb_Elements gives the offset of the last positional element.
1710 if Present (Component_Associations (N)) then
1711 Assoc := Last (Component_Associations (N));
1713 -- Ada 2005 (AI-287)
1715 if Box_Present (Assoc) then
1716 Append_List (Gen_While (Add (Nb_Elements, To => Aggr_L),
1717 Aggr_High,
1718 Empty),
1719 To => New_Code);
1720 else
1721 Expr := Expression (Assoc);
1723 Append_List (Gen_While (Add (Nb_Elements, To => Aggr_L),
1724 Aggr_High,
1725 Expr), -- AI-287
1726 To => New_Code);
1727 end if;
1728 end if;
1729 end if;
1731 return New_Code;
1732 end Build_Array_Aggr_Code;
1734 ----------------------------
1735 -- Build_Record_Aggr_Code --
1736 ----------------------------
1738 function Build_Record_Aggr_Code
1739 (N : Node_Id;
1740 Typ : Entity_Id;
1741 Lhs : Node_Id;
1742 Flist : Node_Id := Empty;
1743 Obj : Entity_Id := Empty;
1744 Is_Limited_Ancestor_Expansion : Boolean := False) return List_Id
1746 Loc : constant Source_Ptr := Sloc (N);
1747 L : constant List_Id := New_List;
1748 N_Typ : constant Entity_Id := Etype (N);
1750 Comp : Node_Id;
1751 Instr : Node_Id;
1752 Ref : Node_Id;
1753 Target : Entity_Id;
1754 F : Node_Id;
1755 Comp_Type : Entity_Id;
1756 Selector : Entity_Id;
1757 Comp_Expr : Node_Id;
1758 Expr_Q : Node_Id;
1760 Internal_Final_List : Node_Id := Empty;
1762 -- If this is an internal aggregate, the External_Final_List is an
1763 -- expression for the controller record of the enclosing type.
1765 -- If the current aggregate has several controlled components, this
1766 -- expression will appear in several calls to attach to the finali-
1767 -- zation list, and it must not be shared.
1769 External_Final_List : Node_Id;
1770 Ancestor_Is_Expression : Boolean := False;
1771 Ancestor_Is_Subtype_Mark : Boolean := False;
1773 Init_Typ : Entity_Id := Empty;
1774 Attach : Node_Id;
1776 Ctrl_Stuff_Done : Boolean := False;
1777 -- True if Gen_Ctrl_Actions_For_Aggr has already been called; calls
1778 -- after the first do nothing.
1780 function Ancestor_Discriminant_Value (Disc : Entity_Id) return Node_Id;
1781 -- Returns the value that the given discriminant of an ancestor type
1782 -- should receive (in the absence of a conflict with the value provided
1783 -- by an ancestor part of an extension aggregate).
1785 procedure Check_Ancestor_Discriminants (Anc_Typ : Entity_Id);
1786 -- Check that each of the discriminant values defined by the ancestor
1787 -- part of an extension aggregate match the corresponding values
1788 -- provided by either an association of the aggregate or by the
1789 -- constraint imposed by a parent type (RM95-4.3.2(8)).
1791 function Compatible_Int_Bounds
1792 (Agg_Bounds : Node_Id;
1793 Typ_Bounds : Node_Id) return Boolean;
1794 -- Return true if Agg_Bounds are equal or within Typ_Bounds. It is
1795 -- assumed that both bounds are integer ranges.
1797 procedure Gen_Ctrl_Actions_For_Aggr;
1798 -- Deal with the various controlled type data structure initializations
1799 -- (but only if it hasn't been done already).
1801 function Get_Constraint_Association (T : Entity_Id) return Node_Id;
1802 -- Returns the first discriminant association in the constraint
1803 -- associated with T, if any, otherwise returns Empty.
1805 function Init_Controller
1806 (Target : Node_Id;
1807 Typ : Entity_Id;
1808 F : Node_Id;
1809 Attach : Node_Id;
1810 Init_Pr : Boolean) return List_Id;
1811 -- Returns the list of statements necessary to initialize the internal
1812 -- controller of the (possible) ancestor typ into target and attach it
1813 -- to finalization list F. Init_Pr conditions the call to the init proc
1814 -- since it may already be done due to ancestor initialization.
1816 function Is_Int_Range_Bounds (Bounds : Node_Id) return Boolean;
1817 -- Check whether Bounds is a range node and its lower and higher bounds
1818 -- are integers literals.
1820 ---------------------------------
1821 -- Ancestor_Discriminant_Value --
1822 ---------------------------------
1824 function Ancestor_Discriminant_Value (Disc : Entity_Id) return Node_Id is
1825 Assoc : Node_Id;
1826 Assoc_Elmt : Elmt_Id;
1827 Aggr_Comp : Entity_Id;
1828 Corresp_Disc : Entity_Id;
1829 Current_Typ : Entity_Id := Base_Type (Typ);
1830 Parent_Typ : Entity_Id;
1831 Parent_Disc : Entity_Id;
1832 Save_Assoc : Node_Id := Empty;
1834 begin
1835 -- First check any discriminant associations to see if any of them
1836 -- provide a value for the discriminant.
1838 if Present (Discriminant_Specifications (Parent (Current_Typ))) then
1839 Assoc := First (Component_Associations (N));
1840 while Present (Assoc) loop
1841 Aggr_Comp := Entity (First (Choices (Assoc)));
1843 if Ekind (Aggr_Comp) = E_Discriminant then
1844 Save_Assoc := Expression (Assoc);
1846 Corresp_Disc := Corresponding_Discriminant (Aggr_Comp);
1847 while Present (Corresp_Disc) loop
1849 -- If found a corresponding discriminant then return the
1850 -- value given in the aggregate. (Note: this is not
1851 -- correct in the presence of side effects. ???)
1853 if Disc = Corresp_Disc then
1854 return Duplicate_Subexpr (Expression (Assoc));
1855 end if;
1857 Corresp_Disc :=
1858 Corresponding_Discriminant (Corresp_Disc);
1859 end loop;
1860 end if;
1862 Next (Assoc);
1863 end loop;
1864 end if;
1866 -- No match found in aggregate, so chain up parent types to find
1867 -- a constraint that defines the value of the discriminant.
1869 Parent_Typ := Etype (Current_Typ);
1870 while Current_Typ /= Parent_Typ loop
1871 if Has_Discriminants (Parent_Typ) then
1872 Parent_Disc := First_Discriminant (Parent_Typ);
1874 -- We either get the association from the subtype indication
1875 -- of the type definition itself, or from the discriminant
1876 -- constraint associated with the type entity (which is
1877 -- preferable, but it's not always present ???)
1879 if Is_Empty_Elmt_List (
1880 Discriminant_Constraint (Current_Typ))
1881 then
1882 Assoc := Get_Constraint_Association (Current_Typ);
1883 Assoc_Elmt := No_Elmt;
1884 else
1885 Assoc_Elmt :=
1886 First_Elmt (Discriminant_Constraint (Current_Typ));
1887 Assoc := Node (Assoc_Elmt);
1888 end if;
1890 -- Traverse the discriminants of the parent type looking
1891 -- for one that corresponds.
1893 while Present (Parent_Disc) and then Present (Assoc) loop
1894 Corresp_Disc := Parent_Disc;
1895 while Present (Corresp_Disc)
1896 and then Disc /= Corresp_Disc
1897 loop
1898 Corresp_Disc :=
1899 Corresponding_Discriminant (Corresp_Disc);
1900 end loop;
1902 if Disc = Corresp_Disc then
1903 if Nkind (Assoc) = N_Discriminant_Association then
1904 Assoc := Expression (Assoc);
1905 end if;
1907 -- If the located association directly denotes a
1908 -- discriminant, then use the value of a saved
1909 -- association of the aggregate. This is a kludge to
1910 -- handle certain cases involving multiple discriminants
1911 -- mapped to a single discriminant of a descendant. It's
1912 -- not clear how to locate the appropriate discriminant
1913 -- value for such cases. ???
1915 if Is_Entity_Name (Assoc)
1916 and then Ekind (Entity (Assoc)) = E_Discriminant
1917 then
1918 Assoc := Save_Assoc;
1919 end if;
1921 return Duplicate_Subexpr (Assoc);
1922 end if;
1924 Next_Discriminant (Parent_Disc);
1926 if No (Assoc_Elmt) then
1927 Next (Assoc);
1928 else
1929 Next_Elmt (Assoc_Elmt);
1930 if Present (Assoc_Elmt) then
1931 Assoc := Node (Assoc_Elmt);
1932 else
1933 Assoc := Empty;
1934 end if;
1935 end if;
1936 end loop;
1937 end if;
1939 Current_Typ := Parent_Typ;
1940 Parent_Typ := Etype (Current_Typ);
1941 end loop;
1943 -- In some cases there's no ancestor value to locate (such as
1944 -- when an ancestor part given by an expression defines the
1945 -- discriminant value).
1947 return Empty;
1948 end Ancestor_Discriminant_Value;
1950 ----------------------------------
1951 -- Check_Ancestor_Discriminants --
1952 ----------------------------------
1954 procedure Check_Ancestor_Discriminants (Anc_Typ : Entity_Id) is
1955 Discr : Entity_Id;
1956 Disc_Value : Node_Id;
1957 Cond : Node_Id;
1959 begin
1960 Discr := First_Discriminant (Base_Type (Anc_Typ));
1961 while Present (Discr) loop
1962 Disc_Value := Ancestor_Discriminant_Value (Discr);
1964 if Present (Disc_Value) then
1965 Cond := Make_Op_Ne (Loc,
1966 Left_Opnd =>
1967 Make_Selected_Component (Loc,
1968 Prefix => New_Copy_Tree (Target),
1969 Selector_Name => New_Occurrence_Of (Discr, Loc)),
1970 Right_Opnd => Disc_Value);
1972 Append_To (L,
1973 Make_Raise_Constraint_Error (Loc,
1974 Condition => Cond,
1975 Reason => CE_Discriminant_Check_Failed));
1976 end if;
1978 Next_Discriminant (Discr);
1979 end loop;
1980 end Check_Ancestor_Discriminants;
1982 ---------------------------
1983 -- Compatible_Int_Bounds --
1984 ---------------------------
1986 function Compatible_Int_Bounds
1987 (Agg_Bounds : Node_Id;
1988 Typ_Bounds : Node_Id) return Boolean
1990 Agg_Lo : constant Uint := Intval (Low_Bound (Agg_Bounds));
1991 Agg_Hi : constant Uint := Intval (High_Bound (Agg_Bounds));
1992 Typ_Lo : constant Uint := Intval (Low_Bound (Typ_Bounds));
1993 Typ_Hi : constant Uint := Intval (High_Bound (Typ_Bounds));
1994 begin
1995 return Typ_Lo <= Agg_Lo and then Agg_Hi <= Typ_Hi;
1996 end Compatible_Int_Bounds;
1998 --------------------------------
1999 -- Get_Constraint_Association --
2000 --------------------------------
2002 function Get_Constraint_Association (T : Entity_Id) return Node_Id is
2003 Typ_Def : constant Node_Id := Type_Definition (Parent (T));
2004 Indic : constant Node_Id := Subtype_Indication (Typ_Def);
2006 begin
2007 -- ??? Also need to cover case of a type mark denoting a subtype
2008 -- with constraint.
2010 if Nkind (Indic) = N_Subtype_Indication
2011 and then Present (Constraint (Indic))
2012 then
2013 return First (Constraints (Constraint (Indic)));
2014 end if;
2016 return Empty;
2017 end Get_Constraint_Association;
2019 ---------------------
2020 -- Init_Controller --
2021 ---------------------
2023 function Init_Controller
2024 (Target : Node_Id;
2025 Typ : Entity_Id;
2026 F : Node_Id;
2027 Attach : Node_Id;
2028 Init_Pr : Boolean) return List_Id
2030 L : constant List_Id := New_List;
2031 Ref : Node_Id;
2032 RC : RE_Id;
2033 Target_Type : Entity_Id;
2035 begin
2036 -- Generate:
2037 -- init-proc (target._controller);
2038 -- initialize (target._controller);
2039 -- Attach_to_Final_List (target._controller, F);
2041 Ref :=
2042 Make_Selected_Component (Loc,
2043 Prefix => Convert_To (Typ, New_Copy_Tree (Target)),
2044 Selector_Name => Make_Identifier (Loc, Name_uController));
2045 Set_Assignment_OK (Ref);
2047 -- Ada 2005 (AI-287): Give support to aggregates of limited types.
2048 -- If the type is intrinsically limited the controller is limited as
2049 -- well. If it is tagged and limited then so is the controller.
2050 -- Otherwise an untagged type may have limited components without its
2051 -- full view being limited, so the controller is not limited.
2053 if Nkind (Target) = N_Identifier then
2054 Target_Type := Etype (Target);
2056 elsif Nkind (Target) = N_Selected_Component then
2057 Target_Type := Etype (Selector_Name (Target));
2059 elsif Nkind (Target) = N_Unchecked_Type_Conversion then
2060 Target_Type := Etype (Target);
2062 elsif Nkind (Target) = N_Unchecked_Expression
2063 and then Nkind (Expression (Target)) = N_Indexed_Component
2064 then
2065 Target_Type := Etype (Prefix (Expression (Target)));
2067 else
2068 Target_Type := Etype (Target);
2069 end if;
2071 -- If the target has not been analyzed yet, as will happen with
2072 -- delayed expansion, use the given type (either the aggregate type
2073 -- or an ancestor) to determine limitedness.
2075 if No (Target_Type) then
2076 Target_Type := Typ;
2077 end if;
2079 if (Is_Tagged_Type (Target_Type))
2080 and then Is_Limited_Type (Target_Type)
2081 then
2082 RC := RE_Limited_Record_Controller;
2084 elsif Is_Inherently_Limited_Type (Target_Type) then
2085 RC := RE_Limited_Record_Controller;
2087 else
2088 RC := RE_Record_Controller;
2089 end if;
2091 if Init_Pr then
2092 Append_List_To (L,
2093 Build_Initialization_Call (Loc,
2094 Id_Ref => Ref,
2095 Typ => RTE (RC),
2096 In_Init_Proc => Within_Init_Proc));
2097 end if;
2099 Append_To (L,
2100 Make_Procedure_Call_Statement (Loc,
2101 Name =>
2102 New_Reference_To (
2103 Find_Prim_Op (RTE (RC), Name_Initialize), Loc),
2104 Parameter_Associations =>
2105 New_List (New_Copy_Tree (Ref))));
2107 Append_To (L,
2108 Make_Attach_Call (
2109 Obj_Ref => New_Copy_Tree (Ref),
2110 Flist_Ref => F,
2111 With_Attach => Attach));
2113 return L;
2114 end Init_Controller;
2116 -------------------------
2117 -- Is_Int_Range_Bounds --
2118 -------------------------
2120 function Is_Int_Range_Bounds (Bounds : Node_Id) return Boolean is
2121 begin
2122 return Nkind (Bounds) = N_Range
2123 and then Nkind (Low_Bound (Bounds)) = N_Integer_Literal
2124 and then Nkind (High_Bound (Bounds)) = N_Integer_Literal;
2125 end Is_Int_Range_Bounds;
2127 -------------------------------
2128 -- Gen_Ctrl_Actions_For_Aggr --
2129 -------------------------------
2131 procedure Gen_Ctrl_Actions_For_Aggr is
2132 Alloc : Node_Id := Empty;
2134 begin
2135 -- Do the work only the first time this is called
2137 if Ctrl_Stuff_Done then
2138 return;
2139 end if;
2141 Ctrl_Stuff_Done := True;
2143 if Present (Obj)
2144 and then Finalize_Storage_Only (Typ)
2145 and then
2146 (Is_Library_Level_Entity (Obj)
2147 or else Entity (Constant_Value (RTE (RE_Garbage_Collected))) =
2148 Standard_True)
2150 -- why not Is_True (Expr_Value (RTE (RE_Garbaage_Collected) ???
2151 then
2152 Attach := Make_Integer_Literal (Loc, 0);
2154 elsif Nkind (Parent (N)) = N_Qualified_Expression
2155 and then Nkind (Parent (Parent (N))) = N_Allocator
2156 then
2157 Alloc := Parent (Parent (N));
2158 Attach := Make_Integer_Literal (Loc, 2);
2160 else
2161 Attach := Make_Integer_Literal (Loc, 1);
2162 end if;
2164 -- Determine the external finalization list. It is either the
2165 -- finalization list of the outer-scope or the one coming from
2166 -- an outer aggregate. When the target is not a temporary, the
2167 -- proper scope is the scope of the target rather than the
2168 -- potentially transient current scope.
2170 if Needs_Finalization (Typ) then
2172 -- The current aggregate belongs to an allocator which creates
2173 -- an object through an anonymous access type or acts as the root
2174 -- of a coextension chain.
2176 if Present (Alloc)
2177 and then
2178 (Is_Coextension_Root (Alloc)
2179 or else Ekind (Etype (Alloc)) = E_Anonymous_Access_Type)
2180 then
2181 if No (Associated_Final_Chain (Etype (Alloc))) then
2182 Build_Final_List (Alloc, Etype (Alloc));
2183 end if;
2185 External_Final_List :=
2186 Make_Selected_Component (Loc,
2187 Prefix =>
2188 New_Reference_To (
2189 Associated_Final_Chain (Etype (Alloc)), Loc),
2190 Selector_Name =>
2191 Make_Identifier (Loc, Name_F));
2193 elsif Present (Flist) then
2194 External_Final_List := New_Copy_Tree (Flist);
2196 elsif Is_Entity_Name (Target)
2197 and then Present (Scope (Entity (Target)))
2198 then
2199 External_Final_List :=
2200 Find_Final_List (Scope (Entity (Target)));
2202 else
2203 External_Final_List := Find_Final_List (Current_Scope);
2204 end if;
2205 else
2206 External_Final_List := Empty;
2207 end if;
2209 -- Initialize and attach the outer object in the is_controlled case
2211 if Is_Controlled (Typ) then
2212 if Ancestor_Is_Subtype_Mark then
2213 Ref := Convert_To (Init_Typ, New_Copy_Tree (Target));
2214 Set_Assignment_OK (Ref);
2215 Append_To (L,
2216 Make_Procedure_Call_Statement (Loc,
2217 Name =>
2218 New_Reference_To
2219 (Find_Prim_Op (Init_Typ, Name_Initialize), Loc),
2220 Parameter_Associations => New_List (New_Copy_Tree (Ref))));
2221 end if;
2223 if not Has_Controlled_Component (Typ) then
2224 Ref := New_Copy_Tree (Target);
2225 Set_Assignment_OK (Ref);
2227 -- This is an aggregate of a coextension. Do not produce a
2228 -- finalization call, but rather attach the reference of the
2229 -- aggregate to its coextension chain.
2231 if Present (Alloc)
2232 and then Is_Dynamic_Coextension (Alloc)
2233 then
2234 if No (Coextensions (Alloc)) then
2235 Set_Coextensions (Alloc, New_Elmt_List);
2236 end if;
2238 Append_Elmt (Ref, Coextensions (Alloc));
2239 else
2240 Append_To (L,
2241 Make_Attach_Call (
2242 Obj_Ref => Ref,
2243 Flist_Ref => New_Copy_Tree (External_Final_List),
2244 With_Attach => Attach));
2245 end if;
2246 end if;
2247 end if;
2249 -- In the Has_Controlled component case, all the intermediate
2250 -- controllers must be initialized.
2252 if Has_Controlled_Component (Typ)
2253 and not Is_Limited_Ancestor_Expansion
2254 then
2255 declare
2256 Inner_Typ : Entity_Id;
2257 Outer_Typ : Entity_Id;
2258 At_Root : Boolean;
2260 begin
2261 -- Find outer type with a controller
2263 Outer_Typ := Base_Type (Typ);
2264 while Outer_Typ /= Init_Typ
2265 and then not Has_New_Controlled_Component (Outer_Typ)
2266 loop
2267 Outer_Typ := Etype (Outer_Typ);
2268 end loop;
2270 -- Attach it to the outer record controller to the external
2271 -- final list.
2273 if Outer_Typ = Init_Typ then
2274 Append_List_To (L,
2275 Init_Controller (
2276 Target => Target,
2277 Typ => Outer_Typ,
2278 F => External_Final_List,
2279 Attach => Attach,
2280 Init_Pr => False));
2282 At_Root := True;
2283 Inner_Typ := Init_Typ;
2285 else
2286 Append_List_To (L,
2287 Init_Controller (
2288 Target => Target,
2289 Typ => Outer_Typ,
2290 F => External_Final_List,
2291 Attach => Attach,
2292 Init_Pr => True));
2294 Inner_Typ := Etype (Outer_Typ);
2295 At_Root :=
2296 not Is_Tagged_Type (Typ) or else Inner_Typ = Outer_Typ;
2297 end if;
2299 -- The outer object has to be attached as well
2301 if Is_Controlled (Typ) then
2302 Ref := New_Copy_Tree (Target);
2303 Set_Assignment_OK (Ref);
2304 Append_To (L,
2305 Make_Attach_Call (
2306 Obj_Ref => Ref,
2307 Flist_Ref => New_Copy_Tree (External_Final_List),
2308 With_Attach => New_Copy_Tree (Attach)));
2309 end if;
2311 -- Initialize the internal controllers for tagged types with
2312 -- more than one controller.
2314 while not At_Root and then Inner_Typ /= Init_Typ loop
2315 if Has_New_Controlled_Component (Inner_Typ) then
2316 F :=
2317 Make_Selected_Component (Loc,
2318 Prefix =>
2319 Convert_To (Outer_Typ, New_Copy_Tree (Target)),
2320 Selector_Name =>
2321 Make_Identifier (Loc, Name_uController));
2322 F :=
2323 Make_Selected_Component (Loc,
2324 Prefix => F,
2325 Selector_Name => Make_Identifier (Loc, Name_F));
2327 Append_List_To (L,
2328 Init_Controller (
2329 Target => Target,
2330 Typ => Inner_Typ,
2331 F => F,
2332 Attach => Make_Integer_Literal (Loc, 1),
2333 Init_Pr => True));
2334 Outer_Typ := Inner_Typ;
2335 end if;
2337 -- Stop at the root
2339 At_Root := Inner_Typ = Etype (Inner_Typ);
2340 Inner_Typ := Etype (Inner_Typ);
2341 end loop;
2343 -- If not done yet attach the controller of the ancestor part
2345 if Outer_Typ /= Init_Typ
2346 and then Inner_Typ = Init_Typ
2347 and then Has_Controlled_Component (Init_Typ)
2348 then
2349 F :=
2350 Make_Selected_Component (Loc,
2351 Prefix => Convert_To (Outer_Typ, New_Copy_Tree (Target)),
2352 Selector_Name =>
2353 Make_Identifier (Loc, Name_uController));
2354 F :=
2355 Make_Selected_Component (Loc,
2356 Prefix => F,
2357 Selector_Name => Make_Identifier (Loc, Name_F));
2359 Attach := Make_Integer_Literal (Loc, 1);
2360 Append_List_To (L,
2361 Init_Controller (
2362 Target => Target,
2363 Typ => Init_Typ,
2364 F => F,
2365 Attach => Attach,
2366 Init_Pr => False));
2368 -- Note: Init_Pr is False because the ancestor part has
2369 -- already been initialized either way (by default, if
2370 -- given by a type name, otherwise from the expression).
2372 end if;
2373 end;
2374 end if;
2375 end Gen_Ctrl_Actions_For_Aggr;
2377 function Replace_Type (Expr : Node_Id) return Traverse_Result;
2378 -- If the aggregate contains a self-reference, traverse each expression
2379 -- to replace a possible self-reference with a reference to the proper
2380 -- component of the target of the assignment.
2382 ------------------
2383 -- Replace_Type --
2384 ------------------
2386 function Replace_Type (Expr : Node_Id) return Traverse_Result is
2387 begin
2388 -- Note regarding the Root_Type test below: Aggregate components for
2389 -- self-referential types include attribute references to the current
2390 -- instance, of the form: Typ'access, etc.. These references are
2391 -- rewritten as references to the target of the aggregate: the
2392 -- left-hand side of an assignment, the entity in a declaration,
2393 -- or a temporary. Without this test, we would improperly extended
2394 -- this rewriting to attribute references whose prefix was not the
2395 -- type of the aggregate.
2397 if Nkind (Expr) = N_Attribute_Reference
2398 and then Is_Entity_Name (Prefix (Expr))
2399 and then Is_Type (Entity (Prefix (Expr)))
2400 and then Root_Type (Etype (N)) = Root_Type (Entity (Prefix (Expr)))
2401 then
2402 if Is_Entity_Name (Lhs) then
2403 Rewrite (Prefix (Expr),
2404 New_Occurrence_Of (Entity (Lhs), Loc));
2406 elsif Nkind (Lhs) = N_Selected_Component then
2407 Rewrite (Expr,
2408 Make_Attribute_Reference (Loc,
2409 Attribute_Name => Name_Unrestricted_Access,
2410 Prefix => New_Copy_Tree (Prefix (Lhs))));
2411 Set_Analyzed (Parent (Expr), False);
2413 else
2414 Rewrite (Expr,
2415 Make_Attribute_Reference (Loc,
2416 Attribute_Name => Name_Unrestricted_Access,
2417 Prefix => New_Copy_Tree (Lhs)));
2418 Set_Analyzed (Parent (Expr), False);
2419 end if;
2420 end if;
2422 return OK;
2423 end Replace_Type;
2425 procedure Replace_Self_Reference is
2426 new Traverse_Proc (Replace_Type);
2428 -- Start of processing for Build_Record_Aggr_Code
2430 begin
2431 if Has_Self_Reference (N) then
2432 Replace_Self_Reference (N);
2433 end if;
2435 -- If the target of the aggregate is class-wide, we must convert it
2436 -- to the actual type of the aggregate, so that the proper components
2437 -- are visible. We know already that the types are compatible.
2439 -- There should also be a comment here explaining why the conversion
2440 -- is needed in the case of interfaces.???
2442 if Present (Etype (Lhs))
2443 and then (Is_Interface (Etype (Lhs))
2444 or else 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).
2551 elsif Is_Limited_Type (Etype (A))
2552 and then Nkind (Unqualify (A)) /= N_Function_Call -- aggregate?
2553 and then
2554 (Nkind (Unqualify (A)) /= N_Unchecked_Type_Conversion
2555 or else
2556 Nkind (Expression (Unqualify (A))) /= N_Function_Call)
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 (Unqualify (A)) = N_Aggregate
2592 or else Nkind (Unqualify (A)) = 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 -- Ada 2005 (AI-287): For each default-initialized component generate
2779 -- a call to the corresponding IP subprogram if available.
2781 if Box_Present (Comp)
2782 and then Has_Non_Null_Base_Init_Proc (Etype (Selector))
2783 then
2784 if Ekind (Selector) /= E_Discriminant then
2785 Gen_Ctrl_Actions_For_Aggr;
2786 end if;
2788 -- Ada 2005 (AI-287): If the component type has tasks then
2789 -- generate the activation chain and master entities (except
2790 -- in case of an allocator because in that case these entities
2791 -- are generated by Build_Task_Allocate_Block_With_Init_Stmts).
2793 declare
2794 Ctype : constant Entity_Id := Etype (Selector);
2795 Inside_Allocator : Boolean := False;
2796 P : Node_Id := Parent (N);
2798 begin
2799 if Is_Task_Type (Ctype) or else Has_Task (Ctype) then
2800 while Present (P) loop
2801 if Nkind (P) = N_Allocator then
2802 Inside_Allocator := True;
2803 exit;
2804 end if;
2806 P := Parent (P);
2807 end loop;
2809 if not Inside_Init_Proc and not Inside_Allocator then
2810 Build_Activation_Chain_Entity (N);
2811 end if;
2812 end if;
2813 end;
2815 Append_List_To (L,
2816 Build_Initialization_Call (Loc,
2817 Id_Ref => Make_Selected_Component (Loc,
2818 Prefix => New_Copy_Tree (Target),
2819 Selector_Name => New_Occurrence_Of (Selector,
2820 Loc)),
2821 Typ => Etype (Selector),
2822 Enclos_Type => Typ,
2823 With_Default_Init => True));
2825 goto Next_Comp;
2826 end if;
2828 -- Prepare for component assignment
2830 if Ekind (Selector) /= E_Discriminant
2831 or else Nkind (N) = N_Extension_Aggregate
2832 then
2833 -- All the discriminants have now been assigned
2835 -- This is now a good moment to initialize and attach all the
2836 -- controllers. Their position may depend on the discriminants.
2838 if Ekind (Selector) /= E_Discriminant then
2839 Gen_Ctrl_Actions_For_Aggr;
2840 end if;
2842 Comp_Type := Etype (Selector);
2843 Comp_Expr :=
2844 Make_Selected_Component (Loc,
2845 Prefix => New_Copy_Tree (Target),
2846 Selector_Name => New_Occurrence_Of (Selector, Loc));
2848 if Nkind (Expression (Comp)) = N_Qualified_Expression then
2849 Expr_Q := Expression (Expression (Comp));
2850 else
2851 Expr_Q := Expression (Comp);
2852 end if;
2854 -- The controller is the one of the parent type defining the
2855 -- component (in case of inherited components).
2857 if Needs_Finalization (Comp_Type) then
2858 Internal_Final_List :=
2859 Make_Selected_Component (Loc,
2860 Prefix => Convert_To (
2861 Scope (Original_Record_Component (Selector)),
2862 New_Copy_Tree (Target)),
2863 Selector_Name =>
2864 Make_Identifier (Loc, Name_uController));
2866 Internal_Final_List :=
2867 Make_Selected_Component (Loc,
2868 Prefix => Internal_Final_List,
2869 Selector_Name => Make_Identifier (Loc, Name_F));
2871 -- The internal final list can be part of a constant object
2873 Set_Assignment_OK (Internal_Final_List);
2875 else
2876 Internal_Final_List := Empty;
2877 end if;
2879 -- Now either create the assignment or generate the code for the
2880 -- inner aggregate top-down.
2882 if Is_Delayed_Aggregate (Expr_Q) then
2884 -- We have the following case of aggregate nesting inside
2885 -- an object declaration:
2887 -- type Arr_Typ is array (Integer range <>) of ...;
2889 -- type Rec_Typ (...) is record
2890 -- Obj_Arr_Typ : Arr_Typ (A .. B);
2891 -- end record;
2893 -- Obj_Rec_Typ : Rec_Typ := (...,
2894 -- Obj_Arr_Typ => (X => (...), Y => (...)));
2896 -- The length of the ranges of the aggregate and Obj_Add_Typ
2897 -- are equal (B - A = Y - X), but they do not coincide (X /=
2898 -- A and B /= Y). This case requires array sliding which is
2899 -- performed in the following manner:
2901 -- subtype Arr_Sub is Arr_Typ (X .. Y);
2902 -- Temp : Arr_Sub;
2903 -- Temp (X) := (...);
2904 -- ...
2905 -- Temp (Y) := (...);
2906 -- Obj_Rec_Typ.Obj_Arr_Typ := Temp;
2908 if Ekind (Comp_Type) = E_Array_Subtype
2909 and then Is_Int_Range_Bounds (Aggregate_Bounds (Expr_Q))
2910 and then Is_Int_Range_Bounds (First_Index (Comp_Type))
2911 and then not
2912 Compatible_Int_Bounds
2913 (Agg_Bounds => Aggregate_Bounds (Expr_Q),
2914 Typ_Bounds => First_Index (Comp_Type))
2915 then
2916 -- Create the array subtype with bounds equal to those of
2917 -- the corresponding aggregate.
2919 declare
2920 SubE : constant Entity_Id :=
2921 Make_Defining_Identifier (Loc,
2922 New_Internal_Name ('T'));
2924 SubD : constant Node_Id :=
2925 Make_Subtype_Declaration (Loc,
2926 Defining_Identifier =>
2927 SubE,
2928 Subtype_Indication =>
2929 Make_Subtype_Indication (Loc,
2930 Subtype_Mark => New_Reference_To (
2931 Etype (Comp_Type), Loc),
2932 Constraint =>
2933 Make_Index_Or_Discriminant_Constraint (
2934 Loc, Constraints => New_List (
2935 New_Copy_Tree (Aggregate_Bounds (
2936 Expr_Q))))));
2938 -- Create a temporary array of the above subtype which
2939 -- will be used to capture the aggregate assignments.
2941 TmpE : constant Entity_Id :=
2942 Make_Defining_Identifier (Loc,
2943 New_Internal_Name ('A'));
2945 TmpD : constant Node_Id :=
2946 Make_Object_Declaration (Loc,
2947 Defining_Identifier =>
2948 TmpE,
2949 Object_Definition =>
2950 New_Reference_To (SubE, Loc));
2952 begin
2953 Set_No_Initialization (TmpD);
2954 Append_To (L, SubD);
2955 Append_To (L, TmpD);
2957 -- Expand aggregate into assignments to the temp array
2959 Append_List_To (L,
2960 Late_Expansion (Expr_Q, Comp_Type,
2961 New_Reference_To (TmpE, Loc), Internal_Final_List));
2963 -- Slide
2965 Append_To (L,
2966 Make_Assignment_Statement (Loc,
2967 Name => New_Copy_Tree (Comp_Expr),
2968 Expression => New_Reference_To (TmpE, Loc)));
2970 -- Do not pass the original aggregate to Gigi as is,
2971 -- since it will potentially clobber the front or the end
2972 -- of the array. Setting the expression to empty is safe
2973 -- since all aggregates are expanded into assignments.
2975 if Present (Obj) then
2976 Set_Expression (Parent (Obj), Empty);
2977 end if;
2978 end;
2980 -- Normal case (sliding not required)
2982 else
2983 Append_List_To (L,
2984 Late_Expansion (Expr_Q, Comp_Type, Comp_Expr,
2985 Internal_Final_List));
2986 end if;
2988 -- Expr_Q is not delayed aggregate
2990 else
2991 Instr :=
2992 Make_OK_Assignment_Statement (Loc,
2993 Name => Comp_Expr,
2994 Expression => Expression (Comp));
2996 Set_No_Ctrl_Actions (Instr);
2997 Append_To (L, Instr);
2999 -- Adjust the tag if tagged (because of possible view
3000 -- conversions), unless compiling for a VM where tags are
3001 -- implicit.
3003 -- tmp.comp._tag := comp_typ'tag;
3005 if Is_Tagged_Type (Comp_Type) and then VM_Target = No_VM then
3006 Instr :=
3007 Make_OK_Assignment_Statement (Loc,
3008 Name =>
3009 Make_Selected_Component (Loc,
3010 Prefix => New_Copy_Tree (Comp_Expr),
3011 Selector_Name =>
3012 New_Reference_To
3013 (First_Tag_Component (Comp_Type), Loc)),
3015 Expression =>
3016 Unchecked_Convert_To (RTE (RE_Tag),
3017 New_Reference_To
3018 (Node (First_Elmt (Access_Disp_Table (Comp_Type))),
3019 Loc)));
3021 Append_To (L, Instr);
3022 end if;
3024 -- Adjust and Attach the component to the proper controller
3026 -- Adjust (tmp.comp);
3027 -- Attach_To_Final_List (tmp.comp,
3028 -- comp_typ (tmp)._record_controller.f)
3030 if Needs_Finalization (Comp_Type)
3031 and then not Is_Limited_Type (Comp_Type)
3032 then
3033 Append_List_To (L,
3034 Make_Adjust_Call (
3035 Ref => New_Copy_Tree (Comp_Expr),
3036 Typ => Comp_Type,
3037 Flist_Ref => Internal_Final_List,
3038 With_Attach => Make_Integer_Literal (Loc, 1)));
3039 end if;
3040 end if;
3042 -- ???
3044 elsif Ekind (Selector) = E_Discriminant
3045 and then Nkind (N) /= N_Extension_Aggregate
3046 and then Nkind (Parent (N)) = N_Component_Association
3047 and then Is_Constrained (Typ)
3048 then
3049 -- We must check that the discriminant value imposed by the
3050 -- context is the same as the value given in the subaggregate,
3051 -- because after the expansion into assignments there is no
3052 -- record on which to perform a regular discriminant check.
3054 declare
3055 D_Val : Elmt_Id;
3056 Disc : Entity_Id;
3058 begin
3059 D_Val := First_Elmt (Discriminant_Constraint (Typ));
3060 Disc := First_Discriminant (Typ);
3061 while Chars (Disc) /= Chars (Selector) loop
3062 Next_Discriminant (Disc);
3063 Next_Elmt (D_Val);
3064 end loop;
3066 pragma Assert (Present (D_Val));
3068 -- This check cannot performed for components that are
3069 -- constrained by a current instance, because this is not a
3070 -- value that can be compared with the actual constraint.
3072 if Nkind (Node (D_Val)) /= N_Attribute_Reference
3073 or else not Is_Entity_Name (Prefix (Node (D_Val)))
3074 or else not Is_Type (Entity (Prefix (Node (D_Val))))
3075 then
3076 Append_To (L,
3077 Make_Raise_Constraint_Error (Loc,
3078 Condition =>
3079 Make_Op_Ne (Loc,
3080 Left_Opnd => New_Copy_Tree (Node (D_Val)),
3081 Right_Opnd => Expression (Comp)),
3082 Reason => CE_Discriminant_Check_Failed));
3084 else
3085 -- Find self-reference in previous discriminant assignment,
3086 -- and replace with proper expression.
3088 declare
3089 Ass : Node_Id;
3091 begin
3092 Ass := First (L);
3093 while Present (Ass) loop
3094 if Nkind (Ass) = N_Assignment_Statement
3095 and then Nkind (Name (Ass)) = N_Selected_Component
3096 and then Chars (Selector_Name (Name (Ass))) =
3097 Chars (Disc)
3098 then
3099 Set_Expression
3100 (Ass, New_Copy_Tree (Expression (Comp)));
3101 exit;
3102 end if;
3103 Next (Ass);
3104 end loop;
3105 end;
3106 end if;
3107 end;
3108 end if;
3110 <<Next_Comp>>
3112 Next (Comp);
3113 end loop;
3115 -- If the type is tagged, the tag needs to be initialized (unless
3116 -- compiling for the Java VM where tags are implicit). It is done
3117 -- late in the initialization process because in some cases, we call
3118 -- the init proc of an ancestor which will not leave out the right tag
3120 if Ancestor_Is_Expression then
3121 null;
3123 elsif Is_Tagged_Type (Typ) and then VM_Target = No_VM then
3124 Instr :=
3125 Make_OK_Assignment_Statement (Loc,
3126 Name =>
3127 Make_Selected_Component (Loc,
3128 Prefix => New_Copy_Tree (Target),
3129 Selector_Name =>
3130 New_Reference_To
3131 (First_Tag_Component (Base_Type (Typ)), Loc)),
3133 Expression =>
3134 Unchecked_Convert_To (RTE (RE_Tag),
3135 New_Reference_To
3136 (Node (First_Elmt (Access_Disp_Table (Base_Type (Typ)))),
3137 Loc)));
3139 Append_To (L, Instr);
3141 -- Ada 2005 (AI-251): If the tagged type has been derived from
3142 -- abstract interfaces we must also initialize the tags of the
3143 -- secondary dispatch tables.
3145 if Has_Interfaces (Base_Type (Typ)) then
3146 Init_Secondary_Tags
3147 (Typ => Base_Type (Typ),
3148 Target => Target,
3149 Stmts_List => L);
3150 end if;
3151 end if;
3153 -- If the controllers have not been initialized yet (by lack of non-
3154 -- discriminant components), let's do it now.
3156 Gen_Ctrl_Actions_For_Aggr;
3158 return L;
3159 end Build_Record_Aggr_Code;
3161 -------------------------------
3162 -- Convert_Aggr_In_Allocator --
3163 -------------------------------
3165 procedure Convert_Aggr_In_Allocator
3166 (Alloc : Node_Id;
3167 Decl : Node_Id;
3168 Aggr : Node_Id)
3170 Loc : constant Source_Ptr := Sloc (Aggr);
3171 Typ : constant Entity_Id := Etype (Aggr);
3172 Temp : constant Entity_Id := Defining_Identifier (Decl);
3174 Occ : constant Node_Id :=
3175 Unchecked_Convert_To (Typ,
3176 Make_Explicit_Dereference (Loc,
3177 New_Reference_To (Temp, Loc)));
3179 Access_Type : constant Entity_Id := Etype (Temp);
3180 Flist : Entity_Id;
3182 begin
3183 -- If the allocator is for an access discriminant, there is no
3184 -- finalization list for the anonymous access type, and the eventual
3185 -- finalization of the object is handled through the coextension
3186 -- mechanism. If the enclosing object is not dynamically allocated,
3187 -- the access discriminant is itself placed on the stack. Otherwise,
3188 -- some other finalization list is used (see exp_ch4.adb).
3190 -- Decl has been inserted in the code ahead of the allocator, using
3191 -- Insert_Actions. We use Insert_Actions below as well, to ensure that
3192 -- subsequent insertions are done in the proper order. Using (for
3193 -- example) Insert_Actions_After to place the expanded aggregate
3194 -- immediately after Decl may lead to out-of-order references if the
3195 -- allocator has generated a finalization list, as when the designated
3196 -- object is controlled and there is an open transient scope.
3198 if Ekind (Access_Type) = E_Anonymous_Access_Type
3199 and then Nkind (Associated_Node_For_Itype (Access_Type)) =
3200 N_Discriminant_Specification
3201 then
3202 Flist := Empty;
3203 else
3204 Flist := Find_Final_List (Access_Type);
3205 end if;
3207 if Is_Array_Type (Typ) then
3208 Convert_Array_Aggr_In_Allocator (Decl, Aggr, Occ);
3210 elsif Has_Default_Init_Comps (Aggr) then
3211 declare
3212 L : constant List_Id := New_List;
3213 Init_Stmts : List_Id;
3215 begin
3216 Init_Stmts :=
3217 Late_Expansion
3218 (Aggr, Typ, Occ,
3219 Flist,
3220 Associated_Final_Chain (Base_Type (Access_Type)));
3222 -- ??? Dubious actual for Obj: expect 'the original object being
3223 -- initialized'
3225 if Has_Task (Typ) then
3226 Build_Task_Allocate_Block_With_Init_Stmts (L, Aggr, Init_Stmts);
3227 Insert_Actions (Alloc, L);
3228 else
3229 Insert_Actions (Alloc, Init_Stmts);
3230 end if;
3231 end;
3233 else
3234 Insert_Actions (Alloc,
3235 Late_Expansion
3236 (Aggr, Typ, Occ, Flist,
3237 Associated_Final_Chain (Base_Type (Access_Type))));
3239 -- ??? Dubious actual for Obj: expect 'the original object being
3240 -- initialized'
3242 end if;
3243 end Convert_Aggr_In_Allocator;
3245 --------------------------------
3246 -- Convert_Aggr_In_Assignment --
3247 --------------------------------
3249 procedure Convert_Aggr_In_Assignment (N : Node_Id) is
3250 Aggr : Node_Id := Expression (N);
3251 Typ : constant Entity_Id := Etype (Aggr);
3252 Occ : constant Node_Id := New_Copy_Tree (Name (N));
3254 begin
3255 if Nkind (Aggr) = N_Qualified_Expression then
3256 Aggr := Expression (Aggr);
3257 end if;
3259 Insert_Actions_After (N,
3260 Late_Expansion
3261 (Aggr, Typ, Occ,
3262 Find_Final_List (Typ, New_Copy_Tree (Occ))));
3263 end Convert_Aggr_In_Assignment;
3265 ---------------------------------
3266 -- Convert_Aggr_In_Object_Decl --
3267 ---------------------------------
3269 procedure Convert_Aggr_In_Object_Decl (N : Node_Id) is
3270 Obj : constant Entity_Id := Defining_Identifier (N);
3271 Aggr : Node_Id := Expression (N);
3272 Loc : constant Source_Ptr := Sloc (Aggr);
3273 Typ : constant Entity_Id := Etype (Aggr);
3274 Occ : constant Node_Id := New_Occurrence_Of (Obj, Loc);
3276 function Discriminants_Ok return Boolean;
3277 -- If the object type is constrained, the discriminants in the
3278 -- aggregate must be checked against the discriminants of the subtype.
3279 -- This cannot be done using Apply_Discriminant_Checks because after
3280 -- expansion there is no aggregate left to check.
3282 ----------------------
3283 -- Discriminants_Ok --
3284 ----------------------
3286 function Discriminants_Ok return Boolean is
3287 Cond : Node_Id := Empty;
3288 Check : Node_Id;
3289 D : Entity_Id;
3290 Disc1 : Elmt_Id;
3291 Disc2 : Elmt_Id;
3292 Val1 : Node_Id;
3293 Val2 : Node_Id;
3295 begin
3296 D := First_Discriminant (Typ);
3297 Disc1 := First_Elmt (Discriminant_Constraint (Typ));
3298 Disc2 := First_Elmt (Discriminant_Constraint (Etype (Obj)));
3299 while Present (Disc1) and then Present (Disc2) loop
3300 Val1 := Node (Disc1);
3301 Val2 := Node (Disc2);
3303 if not Is_OK_Static_Expression (Val1)
3304 or else not Is_OK_Static_Expression (Val2)
3305 then
3306 Check := Make_Op_Ne (Loc,
3307 Left_Opnd => Duplicate_Subexpr (Val1),
3308 Right_Opnd => Duplicate_Subexpr (Val2));
3310 if No (Cond) then
3311 Cond := Check;
3313 else
3314 Cond := Make_Or_Else (Loc,
3315 Left_Opnd => Cond,
3316 Right_Opnd => Check);
3317 end if;
3319 elsif Expr_Value (Val1) /= Expr_Value (Val2) then
3320 Apply_Compile_Time_Constraint_Error (Aggr,
3321 Msg => "incorrect value for discriminant&?",
3322 Reason => CE_Discriminant_Check_Failed,
3323 Ent => D);
3324 return False;
3325 end if;
3327 Next_Discriminant (D);
3328 Next_Elmt (Disc1);
3329 Next_Elmt (Disc2);
3330 end loop;
3332 -- If any discriminant constraint is non-static, emit a check
3334 if Present (Cond) then
3335 Insert_Action (N,
3336 Make_Raise_Constraint_Error (Loc,
3337 Condition => Cond,
3338 Reason => CE_Discriminant_Check_Failed));
3339 end if;
3341 return True;
3342 end Discriminants_Ok;
3344 -- Start of processing for Convert_Aggr_In_Object_Decl
3346 begin
3347 Set_Assignment_OK (Occ);
3349 if Nkind (Aggr) = N_Qualified_Expression then
3350 Aggr := Expression (Aggr);
3351 end if;
3353 if Has_Discriminants (Typ)
3354 and then Typ /= Etype (Obj)
3355 and then Is_Constrained (Etype (Obj))
3356 and then not Discriminants_Ok
3357 then
3358 return;
3359 end if;
3361 -- If the context is an extended return statement, it has its own
3362 -- finalization machinery (i.e. works like a transient scope) and
3363 -- we do not want to create an additional one, because objects on
3364 -- the finalization list of the return must be moved to the caller's
3365 -- finalization list to complete the return.
3367 -- However, if the aggregate is limited, it is built in place, and the
3368 -- controlled components are not assigned to intermediate temporaries
3369 -- so there is no need for a transient scope in this case either.
3371 if Requires_Transient_Scope (Typ)
3372 and then Ekind (Current_Scope) /= E_Return_Statement
3373 and then not Is_Limited_Type (Typ)
3374 then
3375 Establish_Transient_Scope
3376 (Aggr,
3377 Sec_Stack =>
3378 Is_Controlled (Typ) or else Has_Controlled_Component (Typ));
3379 end if;
3381 Insert_Actions_After (N, Late_Expansion (Aggr, Typ, Occ, Obj => Obj));
3382 Set_No_Initialization (N);
3383 Initialize_Discriminants (N, Typ);
3384 end Convert_Aggr_In_Object_Decl;
3386 -------------------------------------
3387 -- Convert_Array_Aggr_In_Allocator --
3388 -------------------------------------
3390 procedure Convert_Array_Aggr_In_Allocator
3391 (Decl : Node_Id;
3392 Aggr : Node_Id;
3393 Target : Node_Id)
3395 Aggr_Code : List_Id;
3396 Typ : constant Entity_Id := Etype (Aggr);
3397 Ctyp : constant Entity_Id := Component_Type (Typ);
3399 begin
3400 -- The target is an explicit dereference of the allocated object.
3401 -- Generate component assignments to it, as for an aggregate that
3402 -- appears on the right-hand side of an assignment statement.
3404 Aggr_Code :=
3405 Build_Array_Aggr_Code (Aggr,
3406 Ctype => Ctyp,
3407 Index => First_Index (Typ),
3408 Into => Target,
3409 Scalar_Comp => Is_Scalar_Type (Ctyp));
3411 Insert_Actions_After (Decl, Aggr_Code);
3412 end Convert_Array_Aggr_In_Allocator;
3414 ----------------------------
3415 -- Convert_To_Assignments --
3416 ----------------------------
3418 procedure Convert_To_Assignments (N : Node_Id; Typ : Entity_Id) is
3419 Loc : constant Source_Ptr := Sloc (N);
3420 Temp : Entity_Id;
3422 Instr : Node_Id;
3423 Target_Expr : Node_Id;
3424 Parent_Kind : Node_Kind;
3425 Unc_Decl : Boolean := False;
3426 Parent_Node : Node_Id;
3428 begin
3429 pragma Assert (not Is_Static_Dispatch_Table_Aggregate (N));
3430 pragma Assert (Is_Record_Type (Typ));
3432 Parent_Node := Parent (N);
3433 Parent_Kind := Nkind (Parent_Node);
3435 if Parent_Kind = N_Qualified_Expression then
3437 -- Check if we are in a unconstrained declaration because in this
3438 -- case the current delayed expansion mechanism doesn't work when
3439 -- the declared object size depend on the initializing expr.
3441 begin
3442 Parent_Node := Parent (Parent_Node);
3443 Parent_Kind := Nkind (Parent_Node);
3445 if Parent_Kind = N_Object_Declaration then
3446 Unc_Decl :=
3447 not Is_Entity_Name (Object_Definition (Parent_Node))
3448 or else Has_Discriminants
3449 (Entity (Object_Definition (Parent_Node)))
3450 or else Is_Class_Wide_Type
3451 (Entity (Object_Definition (Parent_Node)));
3452 end if;
3453 end;
3454 end if;
3456 -- Just set the Delay flag in the cases where the transformation will be
3457 -- done top down from above.
3459 if False
3461 -- Internal aggregate (transformed when expanding the parent)
3463 or else Parent_Kind = N_Aggregate
3464 or else Parent_Kind = N_Extension_Aggregate
3465 or else Parent_Kind = N_Component_Association
3467 -- Allocator (see Convert_Aggr_In_Allocator)
3469 or else Parent_Kind = N_Allocator
3471 -- Object declaration (see Convert_Aggr_In_Object_Decl)
3473 or else (Parent_Kind = N_Object_Declaration and then not Unc_Decl)
3475 -- Safe assignment (see Convert_Aggr_Assignments). So far only the
3476 -- assignments in init procs are taken into account.
3478 or else (Parent_Kind = N_Assignment_Statement
3479 and then Inside_Init_Proc)
3481 -- (Ada 2005) An inherently limited type in a return statement,
3482 -- which will be handled in a build-in-place fashion, and may be
3483 -- rewritten as an extended return and have its own finalization
3484 -- machinery. In the case of a simple return, the aggregate needs
3485 -- to be delayed until the scope for the return statement has been
3486 -- created, so that any finalization chain will be associated with
3487 -- that scope. For extended returns, we delay expansion to avoid the
3488 -- creation of an unwanted transient scope that could result in
3489 -- premature finalization of the return object (which is built in
3490 -- in place within the caller's scope).
3492 or else
3493 (Is_Inherently_Limited_Type (Typ)
3494 and then
3495 (Nkind (Parent (Parent_Node)) = N_Extended_Return_Statement
3496 or else Nkind (Parent_Node) = N_Simple_Return_Statement))
3497 then
3498 Set_Expansion_Delayed (N);
3499 return;
3500 end if;
3502 if Requires_Transient_Scope (Typ) then
3503 Establish_Transient_Scope
3504 (N, Sec_Stack =>
3505 Is_Controlled (Typ) or else Has_Controlled_Component (Typ));
3506 end if;
3508 -- If the aggregate is non-limited, create a temporary. If it is
3509 -- limited and the context is an assignment, this is a subaggregate
3510 -- for an enclosing aggregate being expanded. It must be built in place,
3511 -- so use the target of the current assignment.
3513 if Is_Limited_Type (Typ)
3514 and then Nkind (Parent (N)) = N_Assignment_Statement
3515 then
3516 Target_Expr := New_Copy_Tree (Name (Parent (N)));
3517 Insert_Actions
3518 (Parent (N), Build_Record_Aggr_Code (N, Typ, Target_Expr));
3519 Rewrite (Parent (N), Make_Null_Statement (Loc));
3521 else
3522 Temp := Make_Defining_Identifier (Loc, New_Internal_Name ('A'));
3524 Instr :=
3525 Make_Object_Declaration (Loc,
3526 Defining_Identifier => Temp,
3527 Object_Definition => New_Occurrence_Of (Typ, Loc));
3529 Set_No_Initialization (Instr);
3530 Insert_Action (N, Instr);
3531 Initialize_Discriminants (Instr, Typ);
3532 Target_Expr := New_Occurrence_Of (Temp, Loc);
3533 Insert_Actions (N, Build_Record_Aggr_Code (N, Typ, Target_Expr));
3534 Rewrite (N, New_Occurrence_Of (Temp, Loc));
3535 Analyze_And_Resolve (N, Typ);
3536 end if;
3537 end Convert_To_Assignments;
3539 ---------------------------
3540 -- Convert_To_Positional --
3541 ---------------------------
3543 procedure Convert_To_Positional
3544 (N : Node_Id;
3545 Max_Others_Replicate : Nat := 5;
3546 Handle_Bit_Packed : Boolean := False)
3548 Typ : constant Entity_Id := Etype (N);
3550 Static_Components : Boolean := True;
3552 procedure Check_Static_Components;
3553 -- Check whether all components of the aggregate are compile-time known
3554 -- values, and can be passed as is to the back-end without further
3555 -- expansion.
3557 function Flatten
3558 (N : Node_Id;
3559 Ix : Node_Id;
3560 Ixb : Node_Id) return Boolean;
3561 -- Convert the aggregate into a purely positional form if possible. On
3562 -- entry the bounds of all dimensions are known to be static, and the
3563 -- total number of components is safe enough to expand.
3565 function Is_Flat (N : Node_Id; Dims : Int) return Boolean;
3566 -- Return True iff the array N is flat (which is not rivial in the case
3567 -- of multidimensionsl aggregates).
3569 -----------------------------
3570 -- Check_Static_Components --
3571 -----------------------------
3573 procedure Check_Static_Components is
3574 Expr : Node_Id;
3576 begin
3577 Static_Components := True;
3579 if Nkind (N) = N_String_Literal then
3580 null;
3582 elsif Present (Expressions (N)) then
3583 Expr := First (Expressions (N));
3584 while Present (Expr) loop
3585 if Nkind (Expr) /= N_Aggregate
3586 or else not Compile_Time_Known_Aggregate (Expr)
3587 or else Expansion_Delayed (Expr)
3588 then
3589 Static_Components := False;
3590 exit;
3591 end if;
3593 Next (Expr);
3594 end loop;
3595 end if;
3597 if Nkind (N) = N_Aggregate
3598 and then Present (Component_Associations (N))
3599 then
3600 Expr := First (Component_Associations (N));
3601 while Present (Expr) loop
3602 if Nkind (Expression (Expr)) = N_Integer_Literal then
3603 null;
3605 elsif Nkind (Expression (Expr)) /= N_Aggregate
3606 or else
3607 not Compile_Time_Known_Aggregate (Expression (Expr))
3608 or else Expansion_Delayed (Expression (Expr))
3609 then
3610 Static_Components := False;
3611 exit;
3612 end if;
3614 Next (Expr);
3615 end loop;
3616 end if;
3617 end Check_Static_Components;
3619 -------------
3620 -- Flatten --
3621 -------------
3623 function Flatten
3624 (N : Node_Id;
3625 Ix : Node_Id;
3626 Ixb : Node_Id) return Boolean
3628 Loc : constant Source_Ptr := Sloc (N);
3629 Blo : constant Node_Id := Type_Low_Bound (Etype (Ixb));
3630 Lo : constant Node_Id := Type_Low_Bound (Etype (Ix));
3631 Hi : constant Node_Id := Type_High_Bound (Etype (Ix));
3632 Lov : Uint;
3633 Hiv : Uint;
3635 begin
3636 if Nkind (Original_Node (N)) = N_String_Literal then
3637 return True;
3638 end if;
3640 if not Compile_Time_Known_Value (Lo)
3641 or else not Compile_Time_Known_Value (Hi)
3642 then
3643 return False;
3644 end if;
3646 Lov := Expr_Value (Lo);
3647 Hiv := Expr_Value (Hi);
3649 if Hiv < Lov
3650 or else not Compile_Time_Known_Value (Blo)
3651 then
3652 return False;
3653 end if;
3655 -- Determine if set of alternatives is suitable for conversion and
3656 -- build an array containing the values in sequence.
3658 declare
3659 Vals : array (UI_To_Int (Lov) .. UI_To_Int (Hiv))
3660 of Node_Id := (others => Empty);
3661 -- The values in the aggregate sorted appropriately
3663 Vlist : List_Id;
3664 -- Same data as Vals in list form
3666 Rep_Count : Nat;
3667 -- Used to validate Max_Others_Replicate limit
3669 Elmt : Node_Id;
3670 Num : Int := UI_To_Int (Lov);
3671 Choice : Node_Id;
3672 Lo, Hi : Node_Id;
3674 begin
3675 if Present (Expressions (N)) then
3676 Elmt := First (Expressions (N));
3677 while Present (Elmt) loop
3678 if Nkind (Elmt) = N_Aggregate
3679 and then Present (Next_Index (Ix))
3680 and then
3681 not Flatten (Elmt, Next_Index (Ix), Next_Index (Ixb))
3682 then
3683 return False;
3684 end if;
3686 Vals (Num) := Relocate_Node (Elmt);
3687 Num := Num + 1;
3689 Next (Elmt);
3690 end loop;
3691 end if;
3693 if No (Component_Associations (N)) then
3694 return True;
3695 end if;
3697 Elmt := First (Component_Associations (N));
3699 if Nkind (Expression (Elmt)) = N_Aggregate then
3700 if Present (Next_Index (Ix))
3701 and then
3702 not Flatten
3703 (Expression (Elmt), Next_Index (Ix), Next_Index (Ixb))
3704 then
3705 return False;
3706 end if;
3707 end if;
3709 Component_Loop : while Present (Elmt) loop
3710 Choice := First (Choices (Elmt));
3711 Choice_Loop : while Present (Choice) loop
3713 -- If we have an others choice, fill in the missing elements
3714 -- subject to the limit established by Max_Others_Replicate.
3716 if Nkind (Choice) = N_Others_Choice then
3717 Rep_Count := 0;
3719 for J in Vals'Range loop
3720 if No (Vals (J)) then
3721 Vals (J) := New_Copy_Tree (Expression (Elmt));
3722 Rep_Count := Rep_Count + 1;
3724 -- Check for maximum others replication. Note that
3725 -- we skip this test if either of the restrictions
3726 -- No_Elaboration_Code or No_Implicit_Loops is
3727 -- active, or if this is a preelaborable unit.
3729 declare
3730 P : constant Entity_Id :=
3731 Cunit_Entity (Current_Sem_Unit);
3733 begin
3734 if Restriction_Active (No_Elaboration_Code)
3735 or else Restriction_Active (No_Implicit_Loops)
3736 or else Is_Preelaborated (P)
3737 or else (Ekind (P) = E_Package_Body
3738 and then
3739 Is_Preelaborated (Spec_Entity (P)))
3740 then
3741 null;
3743 elsif Rep_Count > Max_Others_Replicate then
3744 return False;
3745 end if;
3746 end;
3747 end if;
3748 end loop;
3750 exit Component_Loop;
3752 -- Case of a subtype mark
3754 elsif Nkind (Choice) = N_Identifier
3755 and then Is_Type (Entity (Choice))
3756 then
3757 Lo := Type_Low_Bound (Etype (Choice));
3758 Hi := Type_High_Bound (Etype (Choice));
3760 -- Case of subtype indication
3762 elsif Nkind (Choice) = N_Subtype_Indication then
3763 Lo := Low_Bound (Range_Expression (Constraint (Choice)));
3764 Hi := High_Bound (Range_Expression (Constraint (Choice)));
3766 -- Case of a range
3768 elsif Nkind (Choice) = N_Range then
3769 Lo := Low_Bound (Choice);
3770 Hi := High_Bound (Choice);
3772 -- Normal subexpression case
3774 else pragma Assert (Nkind (Choice) in N_Subexpr);
3775 if not Compile_Time_Known_Value (Choice) then
3776 return False;
3778 else
3779 Vals (UI_To_Int (Expr_Value (Choice))) :=
3780 New_Copy_Tree (Expression (Elmt));
3781 goto Continue;
3782 end if;
3783 end if;
3785 -- Range cases merge with Lo,Hi said
3787 if not Compile_Time_Known_Value (Lo)
3788 or else
3789 not Compile_Time_Known_Value (Hi)
3790 then
3791 return False;
3792 else
3793 for J in UI_To_Int (Expr_Value (Lo)) ..
3794 UI_To_Int (Expr_Value (Hi))
3795 loop
3796 Vals (J) := New_Copy_Tree (Expression (Elmt));
3797 end loop;
3798 end if;
3800 <<Continue>>
3801 Next (Choice);
3802 end loop Choice_Loop;
3804 Next (Elmt);
3805 end loop Component_Loop;
3807 -- If we get here the conversion is possible
3809 Vlist := New_List;
3810 for J in Vals'Range loop
3811 Append (Vals (J), Vlist);
3812 end loop;
3814 Rewrite (N, Make_Aggregate (Loc, Expressions => Vlist));
3815 Set_Aggregate_Bounds (N, Aggregate_Bounds (Original_Node (N)));
3816 return True;
3817 end;
3818 end Flatten;
3820 -------------
3821 -- Is_Flat --
3822 -------------
3824 function Is_Flat (N : Node_Id; Dims : Int) return Boolean is
3825 Elmt : Node_Id;
3827 begin
3828 if Dims = 0 then
3829 return True;
3831 elsif Nkind (N) = N_Aggregate then
3832 if Present (Component_Associations (N)) then
3833 return False;
3835 else
3836 Elmt := First (Expressions (N));
3837 while Present (Elmt) loop
3838 if not Is_Flat (Elmt, Dims - 1) then
3839 return False;
3840 end if;
3842 Next (Elmt);
3843 end loop;
3845 return True;
3846 end if;
3847 else
3848 return True;
3849 end if;
3850 end Is_Flat;
3852 -- Start of processing for Convert_To_Positional
3854 begin
3855 -- Ada 2005 (AI-287): Do not convert in case of default initialized
3856 -- components because in this case will need to call the corresponding
3857 -- IP procedure.
3859 if Has_Default_Init_Comps (N) then
3860 return;
3861 end if;
3863 if Is_Flat (N, Number_Dimensions (Typ)) then
3864 return;
3865 end if;
3867 if Is_Bit_Packed_Array (Typ)
3868 and then not Handle_Bit_Packed
3869 then
3870 return;
3871 end if;
3873 -- Do not convert to positional if controlled components are involved
3874 -- since these require special processing
3876 if Has_Controlled_Component (Typ) then
3877 return;
3878 end if;
3880 Check_Static_Components;
3882 -- If the size is known, or all the components are static, try to
3883 -- build a fully positional aggregate.
3885 -- The size of the type may not be known for an aggregate with
3886 -- discriminated array components, but if the components are static
3887 -- it is still possible to verify statically that the length is
3888 -- compatible with the upper bound of the type, and therefore it is
3889 -- worth flattening such aggregates as well.
3891 -- For now the back-end expands these aggregates into individual
3892 -- assignments to the target anyway, but it is conceivable that
3893 -- it will eventually be able to treat such aggregates statically???
3895 if Aggr_Size_OK (N, Typ)
3896 and then Flatten (N, First_Index (Typ), First_Index (Base_Type (Typ)))
3897 then
3898 if Static_Components then
3899 Set_Compile_Time_Known_Aggregate (N);
3900 Set_Expansion_Delayed (N, False);
3901 end if;
3903 Analyze_And_Resolve (N, Typ);
3904 end if;
3905 end Convert_To_Positional;
3907 ----------------------------
3908 -- Expand_Array_Aggregate --
3909 ----------------------------
3911 -- Array aggregate expansion proceeds as follows:
3913 -- 1. If requested we generate code to perform all the array aggregate
3914 -- bound checks, specifically
3916 -- (a) Check that the index range defined by aggregate bounds is
3917 -- compatible with corresponding index subtype.
3919 -- (b) If an others choice is present check that no aggregate
3920 -- index is outside the bounds of the index constraint.
3922 -- (c) For multidimensional arrays make sure that all subaggregates
3923 -- corresponding to the same dimension have the same bounds.
3925 -- 2. Check for packed array aggregate which can be converted to a
3926 -- constant so that the aggregate disappeares completely.
3928 -- 3. Check case of nested aggregate. Generally nested aggregates are
3929 -- handled during the processing of the parent aggregate.
3931 -- 4. Check if the aggregate can be statically processed. If this is the
3932 -- case pass it as is to Gigi. Note that a necessary condition for
3933 -- static processing is that the aggregate be fully positional.
3935 -- 5. If in place aggregate expansion is possible (i.e. no need to create
3936 -- a temporary) then mark the aggregate as such and return. Otherwise
3937 -- create a new temporary and generate the appropriate initialization
3938 -- code.
3940 procedure Expand_Array_Aggregate (N : Node_Id) is
3941 Loc : constant Source_Ptr := Sloc (N);
3943 Typ : constant Entity_Id := Etype (N);
3944 Ctyp : constant Entity_Id := Component_Type (Typ);
3945 -- Typ is the correct constrained array subtype of the aggregate
3946 -- Ctyp is the corresponding component type.
3948 Aggr_Dimension : constant Pos := Number_Dimensions (Typ);
3949 -- Number of aggregate index dimensions
3951 Aggr_Low : array (1 .. Aggr_Dimension) of Node_Id;
3952 Aggr_High : array (1 .. Aggr_Dimension) of Node_Id;
3953 -- Low and High bounds of the constraint for each aggregate index
3955 Aggr_Index_Typ : array (1 .. Aggr_Dimension) of Entity_Id;
3956 -- The type of each index
3958 Maybe_In_Place_OK : Boolean;
3959 -- If the type is neither controlled nor packed and the aggregate
3960 -- is the expression in an assignment, assignment in place may be
3961 -- possible, provided other conditions are met on the LHS.
3963 Others_Present : array (1 .. Aggr_Dimension) of Boolean :=
3964 (others => False);
3965 -- If Others_Present (J) is True, then there is an others choice
3966 -- in one of the sub-aggregates of N at dimension J.
3968 procedure Build_Constrained_Type (Positional : Boolean);
3969 -- If the subtype is not static or unconstrained, build a constrained
3970 -- type using the computable sizes of the aggregate and its sub-
3971 -- aggregates.
3973 procedure Check_Bounds (Aggr_Bounds : Node_Id; Index_Bounds : Node_Id);
3974 -- Checks that the bounds of Aggr_Bounds are within the bounds defined
3975 -- by Index_Bounds.
3977 procedure Check_Same_Aggr_Bounds (Sub_Aggr : Node_Id; Dim : Pos);
3978 -- Checks that in a multi-dimensional array aggregate all subaggregates
3979 -- corresponding to the same dimension have the same bounds.
3980 -- Sub_Aggr is an array sub-aggregate. Dim is the dimension
3981 -- corresponding to the sub-aggregate.
3983 procedure Compute_Others_Present (Sub_Aggr : Node_Id; Dim : Pos);
3984 -- Computes the values of array Others_Present. Sub_Aggr is the
3985 -- array sub-aggregate we start the computation from. Dim is the
3986 -- dimension corresponding to the sub-aggregate.
3988 function Has_Address_Clause (D : Node_Id) return Boolean;
3989 -- If the aggregate is the expression in an object declaration, it
3990 -- cannot be expanded in place. This function does a lookahead in the
3991 -- current declarative part to find an address clause for the object
3992 -- being declared.
3994 function In_Place_Assign_OK return Boolean;
3995 -- Simple predicate to determine whether an aggregate assignment can
3996 -- be done in place, because none of the new values can depend on the
3997 -- components of the target of the assignment.
3999 procedure Others_Check (Sub_Aggr : Node_Id; Dim : Pos);
4000 -- Checks that if an others choice is present in any sub-aggregate no
4001 -- aggregate index is outside the bounds of the index constraint.
4002 -- Sub_Aggr is an array sub-aggregate. Dim is the dimension
4003 -- corresponding to the sub-aggregate.
4005 ----------------------------
4006 -- Build_Constrained_Type --
4007 ----------------------------
4009 procedure Build_Constrained_Type (Positional : Boolean) is
4010 Loc : constant Source_Ptr := Sloc (N);
4011 Agg_Type : Entity_Id;
4012 Comp : Node_Id;
4013 Decl : Node_Id;
4014 Typ : constant Entity_Id := Etype (N);
4015 Indices : constant List_Id := New_List;
4016 Num : Int;
4017 Sub_Agg : Node_Id;
4019 begin
4020 Agg_Type :=
4021 Make_Defining_Identifier (
4022 Loc, New_Internal_Name ('A'));
4024 -- If the aggregate is purely positional, all its subaggregates
4025 -- have the same size. We collect the dimensions from the first
4026 -- subaggregate at each level.
4028 if Positional then
4029 Sub_Agg := N;
4031 for D in 1 .. Number_Dimensions (Typ) loop
4032 Sub_Agg := First (Expressions (Sub_Agg));
4034 Comp := Sub_Agg;
4035 Num := 0;
4036 while Present (Comp) loop
4037 Num := Num + 1;
4038 Next (Comp);
4039 end loop;
4041 Append (
4042 Make_Range (Loc,
4043 Low_Bound => Make_Integer_Literal (Loc, 1),
4044 High_Bound =>
4045 Make_Integer_Literal (Loc, Num)),
4046 Indices);
4047 end loop;
4049 else
4050 -- We know the aggregate type is unconstrained and the aggregate
4051 -- is not processable by the back end, therefore not necessarily
4052 -- positional. Retrieve each dimension bounds (computed earlier).
4053 -- earlier.
4055 for D in 1 .. Number_Dimensions (Typ) loop
4056 Append (
4057 Make_Range (Loc,
4058 Low_Bound => Aggr_Low (D),
4059 High_Bound => Aggr_High (D)),
4060 Indices);
4061 end loop;
4062 end if;
4064 Decl :=
4065 Make_Full_Type_Declaration (Loc,
4066 Defining_Identifier => Agg_Type,
4067 Type_Definition =>
4068 Make_Constrained_Array_Definition (Loc,
4069 Discrete_Subtype_Definitions => Indices,
4070 Component_Definition =>
4071 Make_Component_Definition (Loc,
4072 Aliased_Present => False,
4073 Subtype_Indication =>
4074 New_Occurrence_Of (Component_Type (Typ), Loc))));
4076 Insert_Action (N, Decl);
4077 Analyze (Decl);
4078 Set_Etype (N, Agg_Type);
4079 Set_Is_Itype (Agg_Type);
4080 Freeze_Itype (Agg_Type, N);
4081 end Build_Constrained_Type;
4083 ------------------
4084 -- Check_Bounds --
4085 ------------------
4087 procedure Check_Bounds (Aggr_Bounds : Node_Id; Index_Bounds : Node_Id) is
4088 Aggr_Lo : Node_Id;
4089 Aggr_Hi : Node_Id;
4091 Ind_Lo : Node_Id;
4092 Ind_Hi : Node_Id;
4094 Cond : Node_Id := Empty;
4096 begin
4097 Get_Index_Bounds (Aggr_Bounds, Aggr_Lo, Aggr_Hi);
4098 Get_Index_Bounds (Index_Bounds, Ind_Lo, Ind_Hi);
4100 -- Generate the following test:
4102 -- [constraint_error when
4103 -- Aggr_Lo <= Aggr_Hi and then
4104 -- (Aggr_Lo < Ind_Lo or else Aggr_Hi > Ind_Hi)]
4106 -- As an optimization try to see if some tests are trivially vacuous
4107 -- because we are comparing an expression against itself.
4109 if Aggr_Lo = Ind_Lo and then Aggr_Hi = Ind_Hi then
4110 Cond := Empty;
4112 elsif Aggr_Hi = Ind_Hi then
4113 Cond :=
4114 Make_Op_Lt (Loc,
4115 Left_Opnd => Duplicate_Subexpr_Move_Checks (Aggr_Lo),
4116 Right_Opnd => Duplicate_Subexpr_Move_Checks (Ind_Lo));
4118 elsif Aggr_Lo = Ind_Lo then
4119 Cond :=
4120 Make_Op_Gt (Loc,
4121 Left_Opnd => Duplicate_Subexpr_Move_Checks (Aggr_Hi),
4122 Right_Opnd => Duplicate_Subexpr_Move_Checks (Ind_Hi));
4124 else
4125 Cond :=
4126 Make_Or_Else (Loc,
4127 Left_Opnd =>
4128 Make_Op_Lt (Loc,
4129 Left_Opnd => Duplicate_Subexpr_Move_Checks (Aggr_Lo),
4130 Right_Opnd => Duplicate_Subexpr_Move_Checks (Ind_Lo)),
4132 Right_Opnd =>
4133 Make_Op_Gt (Loc,
4134 Left_Opnd => Duplicate_Subexpr (Aggr_Hi),
4135 Right_Opnd => Duplicate_Subexpr (Ind_Hi)));
4136 end if;
4138 if Present (Cond) then
4139 Cond :=
4140 Make_And_Then (Loc,
4141 Left_Opnd =>
4142 Make_Op_Le (Loc,
4143 Left_Opnd => Duplicate_Subexpr_Move_Checks (Aggr_Lo),
4144 Right_Opnd => Duplicate_Subexpr_Move_Checks (Aggr_Hi)),
4146 Right_Opnd => Cond);
4148 Set_Analyzed (Left_Opnd (Left_Opnd (Cond)), False);
4149 Set_Analyzed (Right_Opnd (Left_Opnd (Cond)), False);
4150 Insert_Action (N,
4151 Make_Raise_Constraint_Error (Loc,
4152 Condition => Cond,
4153 Reason => CE_Length_Check_Failed));
4154 end if;
4155 end Check_Bounds;
4157 ----------------------------
4158 -- Check_Same_Aggr_Bounds --
4159 ----------------------------
4161 procedure Check_Same_Aggr_Bounds (Sub_Aggr : Node_Id; Dim : Pos) is
4162 Sub_Lo : constant Node_Id := Low_Bound (Aggregate_Bounds (Sub_Aggr));
4163 Sub_Hi : constant Node_Id := High_Bound (Aggregate_Bounds (Sub_Aggr));
4164 -- The bounds of this specific sub-aggregate
4166 Aggr_Lo : constant Node_Id := Aggr_Low (Dim);
4167 Aggr_Hi : constant Node_Id := Aggr_High (Dim);
4168 -- The bounds of the aggregate for this dimension
4170 Ind_Typ : constant Entity_Id := Aggr_Index_Typ (Dim);
4171 -- The index type for this dimension.xxx
4173 Cond : Node_Id := Empty;
4174 Assoc : Node_Id;
4175 Expr : Node_Id;
4177 begin
4178 -- If index checks are on generate the test
4180 -- [constraint_error when
4181 -- Aggr_Lo /= Sub_Lo or else Aggr_Hi /= Sub_Hi]
4183 -- As an optimization try to see if some tests are trivially vacuos
4184 -- because we are comparing an expression against itself. Also for
4185 -- the first dimension the test is trivially vacuous because there
4186 -- is just one aggregate for dimension 1.
4188 if Index_Checks_Suppressed (Ind_Typ) then
4189 Cond := Empty;
4191 elsif Dim = 1
4192 or else (Aggr_Lo = Sub_Lo and then Aggr_Hi = Sub_Hi)
4193 then
4194 Cond := Empty;
4196 elsif Aggr_Hi = Sub_Hi then
4197 Cond :=
4198 Make_Op_Ne (Loc,
4199 Left_Opnd => Duplicate_Subexpr_Move_Checks (Aggr_Lo),
4200 Right_Opnd => Duplicate_Subexpr_Move_Checks (Sub_Lo));
4202 elsif Aggr_Lo = Sub_Lo then
4203 Cond :=
4204 Make_Op_Ne (Loc,
4205 Left_Opnd => Duplicate_Subexpr_Move_Checks (Aggr_Hi),
4206 Right_Opnd => Duplicate_Subexpr_Move_Checks (Sub_Hi));
4208 else
4209 Cond :=
4210 Make_Or_Else (Loc,
4211 Left_Opnd =>
4212 Make_Op_Ne (Loc,
4213 Left_Opnd => Duplicate_Subexpr_Move_Checks (Aggr_Lo),
4214 Right_Opnd => Duplicate_Subexpr_Move_Checks (Sub_Lo)),
4216 Right_Opnd =>
4217 Make_Op_Ne (Loc,
4218 Left_Opnd => Duplicate_Subexpr (Aggr_Hi),
4219 Right_Opnd => Duplicate_Subexpr (Sub_Hi)));
4220 end if;
4222 if Present (Cond) then
4223 Insert_Action (N,
4224 Make_Raise_Constraint_Error (Loc,
4225 Condition => Cond,
4226 Reason => CE_Length_Check_Failed));
4227 end if;
4229 -- Now look inside the sub-aggregate to see if there is more work
4231 if Dim < Aggr_Dimension then
4233 -- Process positional components
4235 if Present (Expressions (Sub_Aggr)) then
4236 Expr := First (Expressions (Sub_Aggr));
4237 while Present (Expr) loop
4238 Check_Same_Aggr_Bounds (Expr, Dim + 1);
4239 Next (Expr);
4240 end loop;
4241 end if;
4243 -- Process component associations
4245 if Present (Component_Associations (Sub_Aggr)) then
4246 Assoc := First (Component_Associations (Sub_Aggr));
4247 while Present (Assoc) loop
4248 Expr := Expression (Assoc);
4249 Check_Same_Aggr_Bounds (Expr, Dim + 1);
4250 Next (Assoc);
4251 end loop;
4252 end if;
4253 end if;
4254 end Check_Same_Aggr_Bounds;
4256 ----------------------------
4257 -- Compute_Others_Present --
4258 ----------------------------
4260 procedure Compute_Others_Present (Sub_Aggr : Node_Id; Dim : Pos) is
4261 Assoc : Node_Id;
4262 Expr : Node_Id;
4264 begin
4265 if Present (Component_Associations (Sub_Aggr)) then
4266 Assoc := Last (Component_Associations (Sub_Aggr));
4268 if Nkind (First (Choices (Assoc))) = N_Others_Choice then
4269 Others_Present (Dim) := True;
4270 end if;
4271 end if;
4273 -- Now look inside the sub-aggregate to see if there is more work
4275 if Dim < Aggr_Dimension then
4277 -- Process positional components
4279 if Present (Expressions (Sub_Aggr)) then
4280 Expr := First (Expressions (Sub_Aggr));
4281 while Present (Expr) loop
4282 Compute_Others_Present (Expr, Dim + 1);
4283 Next (Expr);
4284 end loop;
4285 end if;
4287 -- Process component associations
4289 if Present (Component_Associations (Sub_Aggr)) then
4290 Assoc := First (Component_Associations (Sub_Aggr));
4291 while Present (Assoc) loop
4292 Expr := Expression (Assoc);
4293 Compute_Others_Present (Expr, Dim + 1);
4294 Next (Assoc);
4295 end loop;
4296 end if;
4297 end if;
4298 end Compute_Others_Present;
4300 ------------------------
4301 -- Has_Address_Clause --
4302 ------------------------
4304 function Has_Address_Clause (D : Node_Id) return Boolean is
4305 Id : constant Entity_Id := Defining_Identifier (D);
4306 Decl : Node_Id;
4308 begin
4309 Decl := Next (D);
4310 while Present (Decl) loop
4311 if Nkind (Decl) = N_At_Clause
4312 and then Chars (Identifier (Decl)) = Chars (Id)
4313 then
4314 return True;
4316 elsif Nkind (Decl) = N_Attribute_Definition_Clause
4317 and then Chars (Decl) = Name_Address
4318 and then Chars (Name (Decl)) = Chars (Id)
4319 then
4320 return True;
4321 end if;
4323 Next (Decl);
4324 end loop;
4326 return False;
4327 end Has_Address_Clause;
4329 ------------------------
4330 -- In_Place_Assign_OK --
4331 ------------------------
4333 function In_Place_Assign_OK return Boolean is
4334 Aggr_In : Node_Id;
4335 Aggr_Lo : Node_Id;
4336 Aggr_Hi : Node_Id;
4337 Obj_In : Node_Id;
4338 Obj_Lo : Node_Id;
4339 Obj_Hi : Node_Id;
4341 function Is_Others_Aggregate (Aggr : Node_Id) return Boolean;
4342 -- Aggregates that consist of a single Others choice are safe
4343 -- if the single expression is.
4345 function Safe_Aggregate (Aggr : Node_Id) return Boolean;
4346 -- Check recursively that each component of a (sub)aggregate does
4347 -- not depend on the variable being assigned to.
4349 function Safe_Component (Expr : Node_Id) return Boolean;
4350 -- Verify that an expression cannot depend on the variable being
4351 -- assigned to. Room for improvement here (but less than before).
4353 -------------------------
4354 -- Is_Others_Aggregate --
4355 -------------------------
4357 function Is_Others_Aggregate (Aggr : Node_Id) return Boolean is
4358 begin
4359 return No (Expressions (Aggr))
4360 and then Nkind
4361 (First (Choices (First (Component_Associations (Aggr)))))
4362 = N_Others_Choice;
4363 end Is_Others_Aggregate;
4365 --------------------
4366 -- Safe_Aggregate --
4367 --------------------
4369 function Safe_Aggregate (Aggr : Node_Id) return Boolean is
4370 Expr : Node_Id;
4372 begin
4373 if Present (Expressions (Aggr)) then
4374 Expr := First (Expressions (Aggr));
4375 while Present (Expr) loop
4376 if Nkind (Expr) = N_Aggregate then
4377 if not Safe_Aggregate (Expr) then
4378 return False;
4379 end if;
4381 elsif not Safe_Component (Expr) then
4382 return False;
4383 end if;
4385 Next (Expr);
4386 end loop;
4387 end if;
4389 if Present (Component_Associations (Aggr)) then
4390 Expr := First (Component_Associations (Aggr));
4391 while Present (Expr) loop
4392 if Nkind (Expression (Expr)) = N_Aggregate then
4393 if not Safe_Aggregate (Expression (Expr)) then
4394 return False;
4395 end if;
4397 elsif not Safe_Component (Expression (Expr)) then
4398 return False;
4399 end if;
4401 Next (Expr);
4402 end loop;
4403 end if;
4405 return True;
4406 end Safe_Aggregate;
4408 --------------------
4409 -- Safe_Component --
4410 --------------------
4412 function Safe_Component (Expr : Node_Id) return Boolean is
4413 Comp : Node_Id := Expr;
4415 function Check_Component (Comp : Node_Id) return Boolean;
4416 -- Do the recursive traversal, after copy
4418 ---------------------
4419 -- Check_Component --
4420 ---------------------
4422 function Check_Component (Comp : Node_Id) return Boolean is
4423 begin
4424 if Is_Overloaded (Comp) then
4425 return False;
4426 end if;
4428 return Compile_Time_Known_Value (Comp)
4430 or else (Is_Entity_Name (Comp)
4431 and then Present (Entity (Comp))
4432 and then No (Renamed_Object (Entity (Comp))))
4434 or else (Nkind (Comp) = N_Attribute_Reference
4435 and then Check_Component (Prefix (Comp)))
4437 or else (Nkind (Comp) in N_Binary_Op
4438 and then Check_Component (Left_Opnd (Comp))
4439 and then Check_Component (Right_Opnd (Comp)))
4441 or else (Nkind (Comp) in N_Unary_Op
4442 and then Check_Component (Right_Opnd (Comp)))
4444 or else (Nkind (Comp) = N_Selected_Component
4445 and then Check_Component (Prefix (Comp)))
4447 or else (Nkind (Comp) = N_Unchecked_Type_Conversion
4448 and then Check_Component (Expression (Comp)));
4449 end Check_Component;
4451 -- Start of processing for Safe_Component
4453 begin
4454 -- If the component appears in an association that may
4455 -- correspond to more than one element, it is not analyzed
4456 -- before the expansion into assignments, to avoid side effects.
4457 -- We analyze, but do not resolve the copy, to obtain sufficient
4458 -- entity information for the checks that follow. If component is
4459 -- overloaded we assume an unsafe function call.
4461 if not Analyzed (Comp) then
4462 if Is_Overloaded (Expr) then
4463 return False;
4465 elsif Nkind (Expr) = N_Aggregate
4466 and then not Is_Others_Aggregate (Expr)
4467 then
4468 return False;
4470 elsif Nkind (Expr) = N_Allocator then
4472 -- For now, too complex to analyze
4474 return False;
4475 end if;
4477 Comp := New_Copy_Tree (Expr);
4478 Set_Parent (Comp, Parent (Expr));
4479 Analyze (Comp);
4480 end if;
4482 if Nkind (Comp) = N_Aggregate then
4483 return Safe_Aggregate (Comp);
4484 else
4485 return Check_Component (Comp);
4486 end if;
4487 end Safe_Component;
4489 -- Start of processing for In_Place_Assign_OK
4491 begin
4492 if Present (Component_Associations (N)) then
4494 -- On assignment, sliding can take place, so we cannot do the
4495 -- assignment in place unless the bounds of the aggregate are
4496 -- statically equal to those of the target.
4498 -- If the aggregate is given by an others choice, the bounds
4499 -- are derived from the left-hand side, and the assignment is
4500 -- safe if the expression is.
4502 if Is_Others_Aggregate (N) then
4503 return
4504 Safe_Component
4505 (Expression (First (Component_Associations (N))));
4506 end if;
4508 Aggr_In := First_Index (Etype (N));
4509 if Nkind (Parent (N)) = N_Assignment_Statement then
4510 Obj_In := First_Index (Etype (Name (Parent (N))));
4512 else
4513 -- Context is an allocator. Check bounds of aggregate
4514 -- against given type in qualified expression.
4516 pragma Assert (Nkind (Parent (Parent (N))) = N_Allocator);
4517 Obj_In :=
4518 First_Index (Etype (Entity (Subtype_Mark (Parent (N)))));
4519 end if;
4521 while Present (Aggr_In) loop
4522 Get_Index_Bounds (Aggr_In, Aggr_Lo, Aggr_Hi);
4523 Get_Index_Bounds (Obj_In, Obj_Lo, Obj_Hi);
4525 if not Compile_Time_Known_Value (Aggr_Lo)
4526 or else not Compile_Time_Known_Value (Aggr_Hi)
4527 or else not Compile_Time_Known_Value (Obj_Lo)
4528 or else not Compile_Time_Known_Value (Obj_Hi)
4529 or else Expr_Value (Aggr_Lo) /= Expr_Value (Obj_Lo)
4530 or else Expr_Value (Aggr_Hi) /= Expr_Value (Obj_Hi)
4531 then
4532 return False;
4533 end if;
4535 Next_Index (Aggr_In);
4536 Next_Index (Obj_In);
4537 end loop;
4538 end if;
4540 -- Now check the component values themselves
4542 return Safe_Aggregate (N);
4543 end In_Place_Assign_OK;
4545 ------------------
4546 -- Others_Check --
4547 ------------------
4549 procedure Others_Check (Sub_Aggr : Node_Id; Dim : Pos) is
4550 Aggr_Lo : constant Node_Id := Aggr_Low (Dim);
4551 Aggr_Hi : constant Node_Id := Aggr_High (Dim);
4552 -- The bounds of the aggregate for this dimension
4554 Ind_Typ : constant Entity_Id := Aggr_Index_Typ (Dim);
4555 -- The index type for this dimension
4557 Need_To_Check : Boolean := False;
4559 Choices_Lo : Node_Id := Empty;
4560 Choices_Hi : Node_Id := Empty;
4561 -- The lowest and highest discrete choices for a named sub-aggregate
4563 Nb_Choices : Int := -1;
4564 -- The number of discrete non-others choices in this sub-aggregate
4566 Nb_Elements : Uint := Uint_0;
4567 -- The number of elements in a positional aggregate
4569 Cond : Node_Id := Empty;
4571 Assoc : Node_Id;
4572 Choice : Node_Id;
4573 Expr : Node_Id;
4575 begin
4576 -- Check if we have an others choice. If we do make sure that this
4577 -- sub-aggregate contains at least one element in addition to the
4578 -- others choice.
4580 if Range_Checks_Suppressed (Ind_Typ) then
4581 Need_To_Check := False;
4583 elsif Present (Expressions (Sub_Aggr))
4584 and then Present (Component_Associations (Sub_Aggr))
4585 then
4586 Need_To_Check := True;
4588 elsif Present (Component_Associations (Sub_Aggr)) then
4589 Assoc := Last (Component_Associations (Sub_Aggr));
4591 if Nkind (First (Choices (Assoc))) /= N_Others_Choice then
4592 Need_To_Check := False;
4594 else
4595 -- Count the number of discrete choices. Start with -1 because
4596 -- the others choice does not count.
4598 Nb_Choices := -1;
4599 Assoc := First (Component_Associations (Sub_Aggr));
4600 while Present (Assoc) loop
4601 Choice := First (Choices (Assoc));
4602 while Present (Choice) loop
4603 Nb_Choices := Nb_Choices + 1;
4604 Next (Choice);
4605 end loop;
4607 Next (Assoc);
4608 end loop;
4610 -- If there is only an others choice nothing to do
4612 Need_To_Check := (Nb_Choices > 0);
4613 end if;
4615 else
4616 Need_To_Check := False;
4617 end if;
4619 -- If we are dealing with a positional sub-aggregate with an others
4620 -- choice then compute the number or positional elements.
4622 if Need_To_Check and then Present (Expressions (Sub_Aggr)) then
4623 Expr := First (Expressions (Sub_Aggr));
4624 Nb_Elements := Uint_0;
4625 while Present (Expr) loop
4626 Nb_Elements := Nb_Elements + 1;
4627 Next (Expr);
4628 end loop;
4630 -- If the aggregate contains discrete choices and an others choice
4631 -- compute the smallest and largest discrete choice values.
4633 elsif Need_To_Check then
4634 Compute_Choices_Lo_And_Choices_Hi : declare
4636 Table : Case_Table_Type (1 .. Nb_Choices);
4637 -- Used to sort all the different choice values
4639 J : Pos := 1;
4640 Low : Node_Id;
4641 High : Node_Id;
4643 begin
4644 Assoc := First (Component_Associations (Sub_Aggr));
4645 while Present (Assoc) loop
4646 Choice := First (Choices (Assoc));
4647 while Present (Choice) loop
4648 if Nkind (Choice) = N_Others_Choice then
4649 exit;
4650 end if;
4652 Get_Index_Bounds (Choice, Low, High);
4653 Table (J).Choice_Lo := Low;
4654 Table (J).Choice_Hi := High;
4656 J := J + 1;
4657 Next (Choice);
4658 end loop;
4660 Next (Assoc);
4661 end loop;
4663 -- Sort the discrete choices
4665 Sort_Case_Table (Table);
4667 Choices_Lo := Table (1).Choice_Lo;
4668 Choices_Hi := Table (Nb_Choices).Choice_Hi;
4669 end Compute_Choices_Lo_And_Choices_Hi;
4670 end if;
4672 -- If no others choice in this sub-aggregate, or the aggregate
4673 -- comprises only an others choice, nothing to do.
4675 if not Need_To_Check then
4676 Cond := Empty;
4678 -- If we are dealing with an aggregate containing an others choice
4679 -- and positional components, we generate the following test:
4681 -- if Ind_Typ'Pos (Aggr_Lo) + (Nb_Elements - 1) >
4682 -- Ind_Typ'Pos (Aggr_Hi)
4683 -- then
4684 -- raise Constraint_Error;
4685 -- end if;
4687 elsif Nb_Elements > Uint_0 then
4688 Cond :=
4689 Make_Op_Gt (Loc,
4690 Left_Opnd =>
4691 Make_Op_Add (Loc,
4692 Left_Opnd =>
4693 Make_Attribute_Reference (Loc,
4694 Prefix => New_Reference_To (Ind_Typ, Loc),
4695 Attribute_Name => Name_Pos,
4696 Expressions =>
4697 New_List
4698 (Duplicate_Subexpr_Move_Checks (Aggr_Lo))),
4699 Right_Opnd => Make_Integer_Literal (Loc, Nb_Elements - 1)),
4701 Right_Opnd =>
4702 Make_Attribute_Reference (Loc,
4703 Prefix => New_Reference_To (Ind_Typ, Loc),
4704 Attribute_Name => Name_Pos,
4705 Expressions => New_List (
4706 Duplicate_Subexpr_Move_Checks (Aggr_Hi))));
4708 -- If we are dealing with an aggregate containing an others choice
4709 -- and discrete choices we generate the following test:
4711 -- [constraint_error when
4712 -- Choices_Lo < Aggr_Lo or else Choices_Hi > Aggr_Hi];
4714 else
4715 Cond :=
4716 Make_Or_Else (Loc,
4717 Left_Opnd =>
4718 Make_Op_Lt (Loc,
4719 Left_Opnd =>
4720 Duplicate_Subexpr_Move_Checks (Choices_Lo),
4721 Right_Opnd =>
4722 Duplicate_Subexpr_Move_Checks (Aggr_Lo)),
4724 Right_Opnd =>
4725 Make_Op_Gt (Loc,
4726 Left_Opnd =>
4727 Duplicate_Subexpr (Choices_Hi),
4728 Right_Opnd =>
4729 Duplicate_Subexpr (Aggr_Hi)));
4730 end if;
4732 if Present (Cond) then
4733 Insert_Action (N,
4734 Make_Raise_Constraint_Error (Loc,
4735 Condition => Cond,
4736 Reason => CE_Length_Check_Failed));
4737 -- Questionable reason code, shouldn't that be a
4738 -- CE_Range_Check_Failed ???
4739 end if;
4741 -- Now look inside the sub-aggregate to see if there is more work
4743 if Dim < Aggr_Dimension then
4745 -- Process positional components
4747 if Present (Expressions (Sub_Aggr)) then
4748 Expr := First (Expressions (Sub_Aggr));
4749 while Present (Expr) loop
4750 Others_Check (Expr, Dim + 1);
4751 Next (Expr);
4752 end loop;
4753 end if;
4755 -- Process component associations
4757 if Present (Component_Associations (Sub_Aggr)) then
4758 Assoc := First (Component_Associations (Sub_Aggr));
4759 while Present (Assoc) loop
4760 Expr := Expression (Assoc);
4761 Others_Check (Expr, Dim + 1);
4762 Next (Assoc);
4763 end loop;
4764 end if;
4765 end if;
4766 end Others_Check;
4768 -- Remaining Expand_Array_Aggregate variables
4770 Tmp : Entity_Id;
4771 -- Holds the temporary aggregate value
4773 Tmp_Decl : Node_Id;
4774 -- Holds the declaration of Tmp
4776 Aggr_Code : List_Id;
4777 Parent_Node : Node_Id;
4778 Parent_Kind : Node_Kind;
4780 -- Start of processing for Expand_Array_Aggregate
4782 begin
4783 -- Do not touch the special aggregates of attributes used for Asm calls
4785 if Is_RTE (Ctyp, RE_Asm_Input_Operand)
4786 or else Is_RTE (Ctyp, RE_Asm_Output_Operand)
4787 then
4788 return;
4789 end if;
4791 -- If the semantic analyzer has determined that aggregate N will raise
4792 -- Constraint_Error at run-time, then the aggregate node has been
4793 -- replaced with an N_Raise_Constraint_Error node and we should
4794 -- never get here.
4796 pragma Assert (not Raises_Constraint_Error (N));
4798 -- STEP 1a
4800 -- Check that the index range defined by aggregate bounds is
4801 -- compatible with corresponding index subtype.
4803 Index_Compatibility_Check : declare
4804 Aggr_Index_Range : Node_Id := First_Index (Typ);
4805 -- The current aggregate index range
4807 Index_Constraint : Node_Id := First_Index (Etype (Typ));
4808 -- The corresponding index constraint against which we have to
4809 -- check the above aggregate index range.
4811 begin
4812 Compute_Others_Present (N, 1);
4814 for J in 1 .. Aggr_Dimension loop
4815 -- There is no need to emit a check if an others choice is
4816 -- present for this array aggregate dimension since in this
4817 -- case one of N's sub-aggregates has taken its bounds from the
4818 -- context and these bounds must have been checked already. In
4819 -- addition all sub-aggregates corresponding to the same
4820 -- dimension must all have the same bounds (checked in (c) below).
4822 if not Range_Checks_Suppressed (Etype (Index_Constraint))
4823 and then not Others_Present (J)
4824 then
4825 -- We don't use Checks.Apply_Range_Check here because it emits
4826 -- a spurious check. Namely it checks that the range defined by
4827 -- the aggregate bounds is non empty. But we know this already
4828 -- if we get here.
4830 Check_Bounds (Aggr_Index_Range, Index_Constraint);
4831 end if;
4833 -- Save the low and high bounds of the aggregate index as well as
4834 -- the index type for later use in checks (b) and (c) below.
4836 Aggr_Low (J) := Low_Bound (Aggr_Index_Range);
4837 Aggr_High (J) := High_Bound (Aggr_Index_Range);
4839 Aggr_Index_Typ (J) := Etype (Index_Constraint);
4841 Next_Index (Aggr_Index_Range);
4842 Next_Index (Index_Constraint);
4843 end loop;
4844 end Index_Compatibility_Check;
4846 -- STEP 1b
4848 -- If an others choice is present check that no aggregate index is
4849 -- outside the bounds of the index constraint.
4851 Others_Check (N, 1);
4853 -- STEP 1c
4855 -- For multidimensional arrays make sure that all subaggregates
4856 -- corresponding to the same dimension have the same bounds.
4858 if Aggr_Dimension > 1 then
4859 Check_Same_Aggr_Bounds (N, 1);
4860 end if;
4862 -- STEP 2
4864 -- Here we test for is packed array aggregate that we can handle at
4865 -- compile time. If so, return with transformation done. Note that we do
4866 -- this even if the aggregate is nested, because once we have done this
4867 -- processing, there is no more nested aggregate!
4869 if Packed_Array_Aggregate_Handled (N) then
4870 return;
4871 end if;
4873 -- At this point we try to convert to positional form
4875 if Ekind (Current_Scope) = E_Package
4876 and then Static_Elaboration_Desired (Current_Scope)
4877 then
4878 Convert_To_Positional (N, Max_Others_Replicate => 100);
4880 else
4881 Convert_To_Positional (N);
4882 end if;
4884 -- if the result is no longer an aggregate (e.g. it may be a string
4885 -- literal, or a temporary which has the needed value), then we are
4886 -- done, since there is no longer a nested aggregate.
4888 if Nkind (N) /= N_Aggregate then
4889 return;
4891 -- We are also done if the result is an analyzed aggregate
4892 -- This case could use more comments ???
4894 elsif Analyzed (N)
4895 and then N /= Original_Node (N)
4896 then
4897 return;
4898 end if;
4900 -- If all aggregate components are compile-time known and the aggregate
4901 -- has been flattened, nothing left to do. The same occurs if the
4902 -- aggregate is used to initialize the components of an statically
4903 -- allocated dispatch table.
4905 if Compile_Time_Known_Aggregate (N)
4906 or else Is_Static_Dispatch_Table_Aggregate (N)
4907 then
4908 Set_Expansion_Delayed (N, False);
4909 return;
4910 end if;
4912 -- Now see if back end processing is possible
4914 if Backend_Processing_Possible (N) then
4916 -- If the aggregate is static but the constraints are not, build
4917 -- a static subtype for the aggregate, so that Gigi can place it
4918 -- in static memory. Perform an unchecked_conversion to the non-
4919 -- static type imposed by the context.
4921 declare
4922 Itype : constant Entity_Id := Etype (N);
4923 Index : Node_Id;
4924 Needs_Type : Boolean := False;
4926 begin
4927 Index := First_Index (Itype);
4928 while Present (Index) loop
4929 if not Is_Static_Subtype (Etype (Index)) then
4930 Needs_Type := True;
4931 exit;
4932 else
4933 Next_Index (Index);
4934 end if;
4935 end loop;
4937 if Needs_Type then
4938 Build_Constrained_Type (Positional => True);
4939 Rewrite (N, Unchecked_Convert_To (Itype, N));
4940 Analyze (N);
4941 end if;
4942 end;
4944 return;
4945 end if;
4947 -- STEP 3
4949 -- Delay expansion for nested aggregates it will be taken care of
4950 -- when the parent aggregate is expanded
4952 Parent_Node := Parent (N);
4953 Parent_Kind := Nkind (Parent_Node);
4955 if Parent_Kind = N_Qualified_Expression then
4956 Parent_Node := Parent (Parent_Node);
4957 Parent_Kind := Nkind (Parent_Node);
4958 end if;
4960 if Parent_Kind = N_Aggregate
4961 or else Parent_Kind = N_Extension_Aggregate
4962 or else Parent_Kind = N_Component_Association
4963 or else (Parent_Kind = N_Object_Declaration
4964 and then Needs_Finalization (Typ))
4965 or else (Parent_Kind = N_Assignment_Statement
4966 and then Inside_Init_Proc)
4967 then
4968 if Static_Array_Aggregate (N)
4969 or else Compile_Time_Known_Aggregate (N)
4970 then
4971 Set_Expansion_Delayed (N, False);
4972 return;
4973 else
4974 Set_Expansion_Delayed (N);
4975 return;
4976 end if;
4977 end if;
4979 -- STEP 4
4981 -- Look if in place aggregate expansion is possible
4983 -- For object declarations we build the aggregate in place, unless
4984 -- the array is bit-packed or the component is controlled.
4986 -- For assignments we do the assignment in place if all the component
4987 -- associations have compile-time known values. For other cases we
4988 -- create a temporary. The analysis for safety of on-line assignment
4989 -- is delicate, i.e. we don't know how to do it fully yet ???
4991 -- For allocators we assign to the designated object in place if the
4992 -- aggregate meets the same conditions as other in-place assignments.
4993 -- In this case the aggregate may not come from source but was created
4994 -- for default initialization, e.g. with Initialize_Scalars.
4996 if Requires_Transient_Scope (Typ) then
4997 Establish_Transient_Scope
4998 (N, Sec_Stack => Has_Controlled_Component (Typ));
4999 end if;
5001 if Has_Default_Init_Comps (N) then
5002 Maybe_In_Place_OK := False;
5004 elsif Is_Bit_Packed_Array (Typ)
5005 or else Has_Controlled_Component (Typ)
5006 then
5007 Maybe_In_Place_OK := False;
5009 else
5010 Maybe_In_Place_OK :=
5011 (Nkind (Parent (N)) = N_Assignment_Statement
5012 and then Comes_From_Source (N)
5013 and then In_Place_Assign_OK)
5015 or else
5016 (Nkind (Parent (Parent (N))) = N_Allocator
5017 and then In_Place_Assign_OK);
5018 end if;
5020 -- If this is an array of tasks, it will be expanded into build-in-
5021 -- -place assignments. Build an activation chain for the tasks now
5023 if Has_Task (Etype (N)) then
5024 Build_Activation_Chain_Entity (N);
5025 end if;
5027 if not Has_Default_Init_Comps (N)
5028 and then Comes_From_Source (Parent (N))
5029 and then Nkind (Parent (N)) = N_Object_Declaration
5030 and then not
5031 Must_Slide (Etype (Defining_Identifier (Parent (N))), Typ)
5032 and then N = Expression (Parent (N))
5033 and then not Is_Bit_Packed_Array (Typ)
5034 and then not Has_Controlled_Component (Typ)
5035 and then not Has_Address_Clause (Parent (N))
5036 then
5037 Tmp := Defining_Identifier (Parent (N));
5038 Set_No_Initialization (Parent (N));
5039 Set_Expression (Parent (N), Empty);
5041 -- Set the type of the entity, for use in the analysis of the
5042 -- subsequent indexed assignments. If the nominal type is not
5043 -- constrained, build a subtype from the known bounds of the
5044 -- aggregate. If the declaration has a subtype mark, use it,
5045 -- otherwise use the itype of the aggregate.
5047 if not Is_Constrained (Typ) then
5048 Build_Constrained_Type (Positional => False);
5049 elsif Is_Entity_Name (Object_Definition (Parent (N)))
5050 and then Is_Constrained (Entity (Object_Definition (Parent (N))))
5051 then
5052 Set_Etype (Tmp, Entity (Object_Definition (Parent (N))));
5053 else
5054 Set_Size_Known_At_Compile_Time (Typ, False);
5055 Set_Etype (Tmp, Typ);
5056 end if;
5058 elsif Maybe_In_Place_OK
5059 and then Nkind (Parent (N)) = N_Qualified_Expression
5060 and then Nkind (Parent (Parent (N))) = N_Allocator
5061 then
5062 Set_Expansion_Delayed (N);
5063 return;
5065 -- In the remaining cases the aggregate is the RHS of an assignment
5067 elsif Maybe_In_Place_OK
5068 and then Is_Entity_Name (Name (Parent (N)))
5069 then
5070 Tmp := Entity (Name (Parent (N)));
5072 if Etype (Tmp) /= Etype (N) then
5073 Apply_Length_Check (N, Etype (Tmp));
5075 if Nkind (N) = N_Raise_Constraint_Error then
5077 -- Static error, nothing further to expand
5079 return;
5080 end if;
5081 end if;
5083 elsif Maybe_In_Place_OK
5084 and then Nkind (Name (Parent (N))) = N_Explicit_Dereference
5085 and then Is_Entity_Name (Prefix (Name (Parent (N))))
5086 then
5087 Tmp := Name (Parent (N));
5089 if Etype (Tmp) /= Etype (N) then
5090 Apply_Length_Check (N, Etype (Tmp));
5091 end if;
5093 elsif Maybe_In_Place_OK
5094 and then Nkind (Name (Parent (N))) = N_Slice
5095 and then Safe_Slice_Assignment (N)
5096 then
5097 -- Safe_Slice_Assignment rewrites assignment as a loop
5099 return;
5101 -- Step 5
5103 -- In place aggregate expansion is not possible
5105 else
5106 Maybe_In_Place_OK := False;
5107 Tmp := Make_Defining_Identifier (Loc, New_Internal_Name ('A'));
5108 Tmp_Decl :=
5109 Make_Object_Declaration
5110 (Loc,
5111 Defining_Identifier => Tmp,
5112 Object_Definition => New_Occurrence_Of (Typ, Loc));
5113 Set_No_Initialization (Tmp_Decl, True);
5115 -- If we are within a loop, the temporary will be pushed on the
5116 -- stack at each iteration. If the aggregate is the expression for
5117 -- an allocator, it will be immediately copied to the heap and can
5118 -- be reclaimed at once. We create a transient scope around the
5119 -- aggregate for this purpose.
5121 if Ekind (Current_Scope) = E_Loop
5122 and then Nkind (Parent (Parent (N))) = N_Allocator
5123 then
5124 Establish_Transient_Scope (N, False);
5125 end if;
5127 Insert_Action (N, Tmp_Decl);
5128 end if;
5130 -- Construct and insert the aggregate code. We can safely suppress
5131 -- index checks because this code is guaranteed not to raise CE
5132 -- on index checks. However we should *not* suppress all checks.
5134 declare
5135 Target : Node_Id;
5137 begin
5138 if Nkind (Tmp) = N_Defining_Identifier then
5139 Target := New_Reference_To (Tmp, Loc);
5141 else
5143 if Has_Default_Init_Comps (N) then
5145 -- Ada 2005 (AI-287): This case has not been analyzed???
5147 raise Program_Error;
5148 end if;
5150 -- Name in assignment is explicit dereference
5152 Target := New_Copy (Tmp);
5153 end if;
5155 Aggr_Code :=
5156 Build_Array_Aggr_Code (N,
5157 Ctype => Ctyp,
5158 Index => First_Index (Typ),
5159 Into => Target,
5160 Scalar_Comp => Is_Scalar_Type (Ctyp));
5161 end;
5163 if Comes_From_Source (Tmp) then
5164 Insert_Actions_After (Parent (N), Aggr_Code);
5166 else
5167 Insert_Actions (N, Aggr_Code);
5168 end if;
5170 -- If the aggregate has been assigned in place, remove the original
5171 -- assignment.
5173 if Nkind (Parent (N)) = N_Assignment_Statement
5174 and then Maybe_In_Place_OK
5175 then
5176 Rewrite (Parent (N), Make_Null_Statement (Loc));
5178 elsif Nkind (Parent (N)) /= N_Object_Declaration
5179 or else Tmp /= Defining_Identifier (Parent (N))
5180 then
5181 Rewrite (N, New_Occurrence_Of (Tmp, Loc));
5182 Analyze_And_Resolve (N, Typ);
5183 end if;
5184 end Expand_Array_Aggregate;
5186 ------------------------
5187 -- Expand_N_Aggregate --
5188 ------------------------
5190 procedure Expand_N_Aggregate (N : Node_Id) is
5191 begin
5192 if Is_Record_Type (Etype (N)) then
5193 Expand_Record_Aggregate (N);
5194 else
5195 Expand_Array_Aggregate (N);
5196 end if;
5197 exception
5198 when RE_Not_Available =>
5199 return;
5200 end Expand_N_Aggregate;
5202 ----------------------------------
5203 -- Expand_N_Extension_Aggregate --
5204 ----------------------------------
5206 -- If the ancestor part is an expression, add a component association for
5207 -- the parent field. If the type of the ancestor part is not the direct
5208 -- parent of the expected type, build recursively the needed ancestors.
5209 -- If the ancestor part is a subtype_mark, replace aggregate with a decla-
5210 -- ration for a temporary of the expected type, followed by individual
5211 -- assignments to the given components.
5213 procedure Expand_N_Extension_Aggregate (N : Node_Id) is
5214 Loc : constant Source_Ptr := Sloc (N);
5215 A : constant Node_Id := Ancestor_Part (N);
5216 Typ : constant Entity_Id := Etype (N);
5218 begin
5219 -- If the ancestor is a subtype mark, an init proc must be called
5220 -- on the resulting object which thus has to be materialized in
5221 -- the front-end
5223 if Is_Entity_Name (A) and then Is_Type (Entity (A)) then
5224 Convert_To_Assignments (N, Typ);
5226 -- The extension aggregate is transformed into a record aggregate
5227 -- of the following form (c1 and c2 are inherited components)
5229 -- (Exp with c3 => a, c4 => b)
5230 -- ==> (c1 => Exp.c1, c2 => Exp.c2, c1 => a, c2 => b)
5232 else
5233 Set_Etype (N, Typ);
5235 if VM_Target = No_VM then
5236 Expand_Record_Aggregate (N,
5237 Orig_Tag =>
5238 New_Occurrence_Of
5239 (Node (First_Elmt (Access_Disp_Table (Typ))), Loc),
5240 Parent_Expr => A);
5241 else
5242 -- No tag is needed in the case of a VM
5243 Expand_Record_Aggregate (N,
5244 Parent_Expr => A);
5245 end if;
5246 end if;
5248 exception
5249 when RE_Not_Available =>
5250 return;
5251 end Expand_N_Extension_Aggregate;
5253 -----------------------------
5254 -- Expand_Record_Aggregate --
5255 -----------------------------
5257 procedure Expand_Record_Aggregate
5258 (N : Node_Id;
5259 Orig_Tag : Node_Id := Empty;
5260 Parent_Expr : Node_Id := Empty)
5262 Loc : constant Source_Ptr := Sloc (N);
5263 Comps : constant List_Id := Component_Associations (N);
5264 Typ : constant Entity_Id := Etype (N);
5265 Base_Typ : constant Entity_Id := Base_Type (Typ);
5267 Static_Components : Boolean := True;
5268 -- Flag to indicate whether all components are compile-time known,
5269 -- and the aggregate can be constructed statically and handled by
5270 -- the back-end.
5272 function Component_Not_OK_For_Backend return Boolean;
5273 -- Check for presence of component which makes it impossible for the
5274 -- backend to process the aggregate, thus requiring the use of a series
5275 -- of assignment statements. Cases checked for are a nested aggregate
5276 -- needing Late_Expansion, the presence of a tagged component which may
5277 -- need tag adjustment, and a bit unaligned component reference.
5279 -- We also force expansion into assignments if a component is of a
5280 -- mutable type (including a private type with discriminants) because
5281 -- in that case the size of the component to be copied may be smaller
5282 -- than the side of the target, and there is no simple way for gigi
5283 -- to compute the size of the object to be copied.
5285 -- NOTE: This is part of the ongoing work to define precisely the
5286 -- interface between front-end and back-end handling of aggregates.
5287 -- In general it is desirable to pass aggregates as they are to gigi,
5288 -- in order to minimize elaboration code. This is one case where the
5289 -- semantics of Ada complicate the analysis and lead to anomalies in
5290 -- the gcc back-end if the aggregate is not expanded into assignments.
5292 ----------------------------------
5293 -- Component_Not_OK_For_Backend --
5294 ----------------------------------
5296 function Component_Not_OK_For_Backend return Boolean is
5297 C : Node_Id;
5298 Expr_Q : Node_Id;
5300 begin
5301 if No (Comps) then
5302 return False;
5303 end if;
5305 C := First (Comps);
5306 while Present (C) loop
5307 if Nkind (Expression (C)) = N_Qualified_Expression then
5308 Expr_Q := Expression (Expression (C));
5309 else
5310 Expr_Q := Expression (C);
5311 end if;
5313 -- Return true if the aggregate has any associations for tagged
5314 -- components that may require tag adjustment.
5316 -- These are cases where the source expression may have a tag that
5317 -- could differ from the component tag (e.g., can occur for type
5318 -- conversions and formal parameters). (Tag adjustment not needed
5319 -- if VM_Target because object tags are implicit in the machine.)
5321 if Is_Tagged_Type (Etype (Expr_Q))
5322 and then (Nkind (Expr_Q) = N_Type_Conversion
5323 or else (Is_Entity_Name (Expr_Q)
5324 and then
5325 Ekind (Entity (Expr_Q)) in Formal_Kind))
5326 and then VM_Target = No_VM
5327 then
5328 Static_Components := False;
5329 return True;
5331 elsif Is_Delayed_Aggregate (Expr_Q) then
5332 Static_Components := False;
5333 return True;
5335 elsif Possible_Bit_Aligned_Component (Expr_Q) then
5336 Static_Components := False;
5337 return True;
5338 end if;
5340 if Is_Scalar_Type (Etype (Expr_Q)) then
5341 if not Compile_Time_Known_Value (Expr_Q) then
5342 Static_Components := False;
5343 end if;
5345 elsif Nkind (Expr_Q) /= N_Aggregate
5346 or else not Compile_Time_Known_Aggregate (Expr_Q)
5347 then
5348 Static_Components := False;
5350 if Is_Private_Type (Etype (Expr_Q))
5351 and then Has_Discriminants (Etype (Expr_Q))
5352 then
5353 return True;
5354 end if;
5355 end if;
5357 Next (C);
5358 end loop;
5360 return False;
5361 end Component_Not_OK_For_Backend;
5363 -- Remaining Expand_Record_Aggregate variables
5365 Tag_Value : Node_Id;
5366 Comp : Entity_Id;
5367 New_Comp : Node_Id;
5369 -- Start of processing for Expand_Record_Aggregate
5371 begin
5372 -- If the aggregate is to be assigned to an atomic variable, we
5373 -- have to prevent a piecemeal assignment even if the aggregate
5374 -- is to be expanded. We create a temporary for the aggregate, and
5375 -- assign the temporary instead, so that the back end can generate
5376 -- an atomic move for it.
5378 if Is_Atomic (Typ)
5379 and then (Nkind (Parent (N)) = N_Object_Declaration
5380 or else Nkind (Parent (N)) = N_Assignment_Statement)
5381 and then Comes_From_Source (Parent (N))
5382 then
5383 Expand_Atomic_Aggregate (N, Typ);
5384 return;
5386 -- No special management required for aggregates used to initialize
5387 -- statically allocated dispatch tables
5389 elsif Is_Static_Dispatch_Table_Aggregate (N) then
5390 return;
5391 end if;
5393 -- Ada 2005 (AI-318-2): We need to convert to assignments if components
5394 -- are build-in-place function calls. This test could be more specific,
5395 -- but doing it for all inherently limited aggregates seems harmless.
5396 -- The assignments will turn into build-in-place function calls (see
5397 -- Make_Build_In_Place_Call_In_Assignment).
5399 if Ada_Version >= Ada_05 and then Is_Inherently_Limited_Type (Typ) then
5400 Convert_To_Assignments (N, Typ);
5402 -- Gigi doesn't handle properly temporaries of variable size
5403 -- so we generate it in the front-end
5405 elsif not Size_Known_At_Compile_Time (Typ) then
5406 Convert_To_Assignments (N, Typ);
5408 -- Temporaries for controlled aggregates need to be attached to a
5409 -- final chain in order to be properly finalized, so it has to
5410 -- be created in the front-end
5412 elsif Is_Controlled (Typ)
5413 or else Has_Controlled_Component (Base_Type (Typ))
5414 then
5415 Convert_To_Assignments (N, Typ);
5417 -- Ada 2005 (AI-287): In case of default initialized components we
5418 -- convert the aggregate into assignments.
5420 elsif Has_Default_Init_Comps (N) then
5421 Convert_To_Assignments (N, Typ);
5423 -- Check components
5425 elsif Component_Not_OK_For_Backend then
5426 Convert_To_Assignments (N, Typ);
5428 -- If an ancestor is private, some components are not inherited and
5429 -- we cannot expand into a record aggregate
5431 elsif Has_Private_Ancestor (Typ) then
5432 Convert_To_Assignments (N, Typ);
5434 -- ??? The following was done to compile fxacc00.ads in the ACVCs. Gigi
5435 -- is not able to handle the aggregate for Late_Request.
5437 elsif Is_Tagged_Type (Typ) and then Has_Discriminants (Typ) then
5438 Convert_To_Assignments (N, Typ);
5440 -- If the tagged types covers interface types we need to initialize all
5441 -- hidden components containing pointers to secondary dispatch tables.
5443 elsif Is_Tagged_Type (Typ) and then Has_Interfaces (Typ) then
5444 Convert_To_Assignments (N, Typ);
5446 -- If some components are mutable, the size of the aggregate component
5447 -- may be distinct from the default size of the type component, so
5448 -- we need to expand to insure that the back-end copies the proper
5449 -- size of the data.
5451 elsif Has_Mutable_Components (Typ) then
5452 Convert_To_Assignments (N, Typ);
5454 -- If the type involved has any non-bit aligned components, then we are
5455 -- not sure that the back end can handle this case correctly.
5457 elsif Type_May_Have_Bit_Aligned_Components (Typ) then
5458 Convert_To_Assignments (N, Typ);
5460 -- In all other cases, build a proper aggregate handlable by gigi
5462 else
5463 if Nkind (N) = N_Aggregate then
5465 -- If the aggregate is static and can be handled by the back-end,
5466 -- nothing left to do.
5468 if Static_Components then
5469 Set_Compile_Time_Known_Aggregate (N);
5470 Set_Expansion_Delayed (N, False);
5471 end if;
5472 end if;
5474 -- If no discriminants, nothing special to do
5476 if not Has_Discriminants (Typ) then
5477 null;
5479 -- Case of discriminants present
5481 elsif Is_Derived_Type (Typ) then
5483 -- For untagged types, non-stored discriminants are replaced
5484 -- with stored discriminants, which are the ones that gigi uses
5485 -- to describe the type and its components.
5487 Generate_Aggregate_For_Derived_Type : declare
5488 Constraints : constant List_Id := New_List;
5489 First_Comp : Node_Id;
5490 Discriminant : Entity_Id;
5491 Decl : Node_Id;
5492 Num_Disc : Int := 0;
5493 Num_Gird : Int := 0;
5495 procedure Prepend_Stored_Values (T : Entity_Id);
5496 -- Scan the list of stored discriminants of the type, and add
5497 -- their values to the aggregate being built.
5499 ---------------------------
5500 -- Prepend_Stored_Values --
5501 ---------------------------
5503 procedure Prepend_Stored_Values (T : Entity_Id) is
5504 begin
5505 Discriminant := First_Stored_Discriminant (T);
5506 while Present (Discriminant) loop
5507 New_Comp :=
5508 Make_Component_Association (Loc,
5509 Choices =>
5510 New_List (New_Occurrence_Of (Discriminant, Loc)),
5512 Expression =>
5513 New_Copy_Tree (
5514 Get_Discriminant_Value (
5515 Discriminant,
5516 Typ,
5517 Discriminant_Constraint (Typ))));
5519 if No (First_Comp) then
5520 Prepend_To (Component_Associations (N), New_Comp);
5521 else
5522 Insert_After (First_Comp, New_Comp);
5523 end if;
5525 First_Comp := New_Comp;
5526 Next_Stored_Discriminant (Discriminant);
5527 end loop;
5528 end Prepend_Stored_Values;
5530 -- Start of processing for Generate_Aggregate_For_Derived_Type
5532 begin
5533 -- Remove the associations for the discriminant of derived type
5535 First_Comp := First (Component_Associations (N));
5536 while Present (First_Comp) loop
5537 Comp := First_Comp;
5538 Next (First_Comp);
5540 if Ekind (Entity
5541 (First (Choices (Comp)))) = E_Discriminant
5542 then
5543 Remove (Comp);
5544 Num_Disc := Num_Disc + 1;
5545 end if;
5546 end loop;
5548 -- Insert stored discriminant associations in the correct
5549 -- order. If there are more stored discriminants than new
5550 -- discriminants, there is at least one new discriminant that
5551 -- constrains more than one of the stored discriminants. In
5552 -- this case we need to construct a proper subtype of the
5553 -- parent type, in order to supply values to all the
5554 -- components. Otherwise there is one-one correspondence
5555 -- between the constraints and the stored discriminants.
5557 First_Comp := Empty;
5559 Discriminant := First_Stored_Discriminant (Base_Type (Typ));
5560 while Present (Discriminant) loop
5561 Num_Gird := Num_Gird + 1;
5562 Next_Stored_Discriminant (Discriminant);
5563 end loop;
5565 -- Case of more stored discriminants than new discriminants
5567 if Num_Gird > Num_Disc then
5569 -- Create a proper subtype of the parent type, which is the
5570 -- proper implementation type for the aggregate, and convert
5571 -- it to the intended target type.
5573 Discriminant := First_Stored_Discriminant (Base_Type (Typ));
5574 while Present (Discriminant) loop
5575 New_Comp :=
5576 New_Copy_Tree (
5577 Get_Discriminant_Value (
5578 Discriminant,
5579 Typ,
5580 Discriminant_Constraint (Typ)));
5581 Append (New_Comp, Constraints);
5582 Next_Stored_Discriminant (Discriminant);
5583 end loop;
5585 Decl :=
5586 Make_Subtype_Declaration (Loc,
5587 Defining_Identifier =>
5588 Make_Defining_Identifier (Loc,
5589 New_Internal_Name ('T')),
5590 Subtype_Indication =>
5591 Make_Subtype_Indication (Loc,
5592 Subtype_Mark =>
5593 New_Occurrence_Of (Etype (Base_Type (Typ)), Loc),
5594 Constraint =>
5595 Make_Index_Or_Discriminant_Constraint
5596 (Loc, Constraints)));
5598 Insert_Action (N, Decl);
5599 Prepend_Stored_Values (Base_Type (Typ));
5601 Set_Etype (N, Defining_Identifier (Decl));
5602 Set_Analyzed (N);
5604 Rewrite (N, Unchecked_Convert_To (Typ, N));
5605 Analyze (N);
5607 -- Case where we do not have fewer new discriminants than
5608 -- stored discriminants, so in this case we can simply use the
5609 -- stored discriminants of the subtype.
5611 else
5612 Prepend_Stored_Values (Typ);
5613 end if;
5614 end Generate_Aggregate_For_Derived_Type;
5615 end if;
5617 if Is_Tagged_Type (Typ) then
5619 -- The tagged case, _parent and _tag component must be created
5621 -- Reset null_present unconditionally. tagged records always have
5622 -- at least one field (the tag or the parent)
5624 Set_Null_Record_Present (N, False);
5626 -- When the current aggregate comes from the expansion of an
5627 -- extension aggregate, the parent expr is replaced by an
5628 -- aggregate formed by selected components of this expr
5630 if Present (Parent_Expr)
5631 and then Is_Empty_List (Comps)
5632 then
5633 Comp := First_Component_Or_Discriminant (Typ);
5634 while Present (Comp) loop
5636 -- Skip all expander-generated components
5639 not Comes_From_Source (Original_Record_Component (Comp))
5640 then
5641 null;
5643 else
5644 New_Comp :=
5645 Make_Selected_Component (Loc,
5646 Prefix =>
5647 Unchecked_Convert_To (Typ,
5648 Duplicate_Subexpr (Parent_Expr, True)),
5650 Selector_Name => New_Occurrence_Of (Comp, Loc));
5652 Append_To (Comps,
5653 Make_Component_Association (Loc,
5654 Choices =>
5655 New_List (New_Occurrence_Of (Comp, Loc)),
5656 Expression =>
5657 New_Comp));
5659 Analyze_And_Resolve (New_Comp, Etype (Comp));
5660 end if;
5662 Next_Component_Or_Discriminant (Comp);
5663 end loop;
5664 end if;
5666 -- Compute the value for the Tag now, if the type is a root it
5667 -- will be included in the aggregate right away, otherwise it will
5668 -- be propagated to the parent aggregate
5670 if Present (Orig_Tag) then
5671 Tag_Value := Orig_Tag;
5672 elsif VM_Target /= No_VM then
5673 Tag_Value := Empty;
5674 else
5675 Tag_Value :=
5676 New_Occurrence_Of
5677 (Node (First_Elmt (Access_Disp_Table (Typ))), Loc);
5678 end if;
5680 -- For a derived type, an aggregate for the parent is formed with
5681 -- all the inherited components.
5683 if Is_Derived_Type (Typ) then
5685 declare
5686 First_Comp : Node_Id;
5687 Parent_Comps : List_Id;
5688 Parent_Aggr : Node_Id;
5689 Parent_Name : Node_Id;
5691 begin
5692 -- Remove the inherited component association from the
5693 -- aggregate and store them in the parent aggregate
5695 First_Comp := First (Component_Associations (N));
5696 Parent_Comps := New_List;
5697 while Present (First_Comp)
5698 and then Scope (Original_Record_Component (
5699 Entity (First (Choices (First_Comp))))) /= Base_Typ
5700 loop
5701 Comp := First_Comp;
5702 Next (First_Comp);
5703 Remove (Comp);
5704 Append (Comp, Parent_Comps);
5705 end loop;
5707 Parent_Aggr := Make_Aggregate (Loc,
5708 Component_Associations => Parent_Comps);
5709 Set_Etype (Parent_Aggr, Etype (Base_Type (Typ)));
5711 -- Find the _parent component
5713 Comp := First_Component (Typ);
5714 while Chars (Comp) /= Name_uParent loop
5715 Comp := Next_Component (Comp);
5716 end loop;
5718 Parent_Name := New_Occurrence_Of (Comp, Loc);
5720 -- Insert the parent aggregate
5722 Prepend_To (Component_Associations (N),
5723 Make_Component_Association (Loc,
5724 Choices => New_List (Parent_Name),
5725 Expression => Parent_Aggr));
5727 -- Expand recursively the parent propagating the right Tag
5729 Expand_Record_Aggregate (
5730 Parent_Aggr, Tag_Value, Parent_Expr);
5731 end;
5733 -- For a root type, the tag component is added (unless compiling
5734 -- for the VMs, where tags are implicit).
5736 elsif VM_Target = No_VM then
5737 declare
5738 Tag_Name : constant Node_Id :=
5739 New_Occurrence_Of
5740 (First_Tag_Component (Typ), Loc);
5741 Typ_Tag : constant Entity_Id := RTE (RE_Tag);
5742 Conv_Node : constant Node_Id :=
5743 Unchecked_Convert_To (Typ_Tag, Tag_Value);
5745 begin
5746 Set_Etype (Conv_Node, Typ_Tag);
5747 Prepend_To (Component_Associations (N),
5748 Make_Component_Association (Loc,
5749 Choices => New_List (Tag_Name),
5750 Expression => Conv_Node));
5751 end;
5752 end if;
5753 end if;
5754 end if;
5756 end Expand_Record_Aggregate;
5758 ----------------------------
5759 -- Has_Default_Init_Comps --
5760 ----------------------------
5762 function Has_Default_Init_Comps (N : Node_Id) return Boolean is
5763 Comps : constant List_Id := Component_Associations (N);
5764 C : Node_Id;
5765 Expr : Node_Id;
5766 begin
5767 pragma Assert (Nkind (N) = N_Aggregate
5768 or else Nkind (N) = N_Extension_Aggregate);
5770 if No (Comps) then
5771 return False;
5772 end if;
5774 if Has_Self_Reference (N) then
5775 return True;
5776 end if;
5778 -- Check if any direct component has default initialized components
5780 C := First (Comps);
5781 while Present (C) loop
5782 if Box_Present (C) then
5783 return True;
5784 end if;
5786 Next (C);
5787 end loop;
5789 -- Recursive call in case of aggregate expression
5791 C := First (Comps);
5792 while Present (C) loop
5793 Expr := Expression (C);
5795 if Present (Expr)
5796 and then (Nkind (Expr) = N_Aggregate
5797 or else Nkind (Expr) = N_Extension_Aggregate)
5798 and then Has_Default_Init_Comps (Expr)
5799 then
5800 return True;
5801 end if;
5803 Next (C);
5804 end loop;
5806 return False;
5807 end Has_Default_Init_Comps;
5809 --------------------------
5810 -- Is_Delayed_Aggregate --
5811 --------------------------
5813 function Is_Delayed_Aggregate (N : Node_Id) return Boolean is
5814 Node : Node_Id := N;
5815 Kind : Node_Kind := Nkind (Node);
5817 begin
5818 if Kind = N_Qualified_Expression then
5819 Node := Expression (Node);
5820 Kind := Nkind (Node);
5821 end if;
5823 if Kind /= N_Aggregate and then Kind /= N_Extension_Aggregate then
5824 return False;
5825 else
5826 return Expansion_Delayed (Node);
5827 end if;
5828 end Is_Delayed_Aggregate;
5830 ----------------------------------------
5831 -- Is_Static_Dispatch_Table_Aggregate --
5832 ----------------------------------------
5834 function Is_Static_Dispatch_Table_Aggregate (N : Node_Id) return Boolean is
5835 Typ : constant Entity_Id := Base_Type (Etype (N));
5837 begin
5838 return Static_Dispatch_Tables
5839 and then VM_Target = No_VM
5840 and then RTU_Loaded (Ada_Tags)
5842 -- Avoid circularity when rebuilding the compiler
5844 and then Cunit_Entity (Get_Source_Unit (N)) /= RTU_Entity (Ada_Tags)
5845 and then (Typ = RTE (RE_Dispatch_Table_Wrapper)
5846 or else
5847 Typ = RTE (RE_Address_Array)
5848 or else
5849 Typ = RTE (RE_Type_Specific_Data)
5850 or else
5851 Typ = RTE (RE_Tag_Table)
5852 or else
5853 (RTE_Available (RE_Interface_Data)
5854 and then Typ = RTE (RE_Interface_Data))
5855 or else
5856 (RTE_Available (RE_Interfaces_Array)
5857 and then Typ = RTE (RE_Interfaces_Array))
5858 or else
5859 (RTE_Available (RE_Interface_Data_Element)
5860 and then Typ = RTE (RE_Interface_Data_Element)));
5861 end Is_Static_Dispatch_Table_Aggregate;
5863 --------------------
5864 -- Late_Expansion --
5865 --------------------
5867 function Late_Expansion
5868 (N : Node_Id;
5869 Typ : Entity_Id;
5870 Target : Node_Id;
5871 Flist : Node_Id := Empty;
5872 Obj : Entity_Id := Empty) return List_Id
5874 begin
5875 if Is_Record_Type (Etype (N)) then
5876 return Build_Record_Aggr_Code (N, Typ, Target, Flist, Obj);
5878 else pragma Assert (Is_Array_Type (Etype (N)));
5879 return
5880 Build_Array_Aggr_Code
5881 (N => N,
5882 Ctype => Component_Type (Etype (N)),
5883 Index => First_Index (Typ),
5884 Into => Target,
5885 Scalar_Comp => Is_Scalar_Type (Component_Type (Typ)),
5886 Indices => No_List,
5887 Flist => Flist);
5888 end if;
5889 end Late_Expansion;
5891 ----------------------------------
5892 -- Make_OK_Assignment_Statement --
5893 ----------------------------------
5895 function Make_OK_Assignment_Statement
5896 (Sloc : Source_Ptr;
5897 Name : Node_Id;
5898 Expression : Node_Id) return Node_Id
5900 begin
5901 Set_Assignment_OK (Name);
5903 return Make_Assignment_Statement (Sloc, Name, Expression);
5904 end Make_OK_Assignment_Statement;
5906 -----------------------
5907 -- Number_Of_Choices --
5908 -----------------------
5910 function Number_Of_Choices (N : Node_Id) return Nat is
5911 Assoc : Node_Id;
5912 Choice : Node_Id;
5914 Nb_Choices : Nat := 0;
5916 begin
5917 if Present (Expressions (N)) then
5918 return 0;
5919 end if;
5921 Assoc := First (Component_Associations (N));
5922 while Present (Assoc) loop
5923 Choice := First (Choices (Assoc));
5924 while Present (Choice) loop
5925 if Nkind (Choice) /= N_Others_Choice then
5926 Nb_Choices := Nb_Choices + 1;
5927 end if;
5929 Next (Choice);
5930 end loop;
5932 Next (Assoc);
5933 end loop;
5935 return Nb_Choices;
5936 end Number_Of_Choices;
5938 ------------------------------------
5939 -- Packed_Array_Aggregate_Handled --
5940 ------------------------------------
5942 -- The current version of this procedure will handle at compile time
5943 -- any array aggregate that meets these conditions:
5945 -- One dimensional, bit packed
5946 -- Underlying packed type is modular type
5947 -- Bounds are within 32-bit Int range
5948 -- All bounds and values are static
5950 function Packed_Array_Aggregate_Handled (N : Node_Id) return Boolean is
5951 Loc : constant Source_Ptr := Sloc (N);
5952 Typ : constant Entity_Id := Etype (N);
5953 Ctyp : constant Entity_Id := Component_Type (Typ);
5955 Not_Handled : exception;
5956 -- Exception raised if this aggregate cannot be handled
5958 begin
5959 -- For now, handle only one dimensional bit packed arrays
5961 if not Is_Bit_Packed_Array (Typ)
5962 or else Number_Dimensions (Typ) > 1
5963 or else not Is_Modular_Integer_Type (Packed_Array_Type (Typ))
5964 then
5965 return False;
5966 end if;
5968 if not Is_Scalar_Type (Component_Type (Typ))
5969 and then Has_Non_Standard_Rep (Component_Type (Typ))
5970 then
5971 return False;
5972 end if;
5974 declare
5975 Csiz : constant Nat := UI_To_Int (Component_Size (Typ));
5977 Lo : Node_Id;
5978 Hi : Node_Id;
5979 -- Bounds of index type
5981 Lob : Uint;
5982 Hib : Uint;
5983 -- Values of bounds if compile time known
5985 function Get_Component_Val (N : Node_Id) return Uint;
5986 -- Given a expression value N of the component type Ctyp, returns a
5987 -- value of Csiz (component size) bits representing this value. If
5988 -- the value is non-static or any other reason exists why the value
5989 -- cannot be returned, then Not_Handled is raised.
5991 -----------------------
5992 -- Get_Component_Val --
5993 -----------------------
5995 function Get_Component_Val (N : Node_Id) return Uint is
5996 Val : Uint;
5998 begin
5999 -- We have to analyze the expression here before doing any further
6000 -- processing here. The analysis of such expressions is deferred
6001 -- till expansion to prevent some problems of premature analysis.
6003 Analyze_And_Resolve (N, Ctyp);
6005 -- Must have a compile time value. String literals have to be
6006 -- converted into temporaries as well, because they cannot easily
6007 -- be converted into their bit representation.
6009 if not Compile_Time_Known_Value (N)
6010 or else Nkind (N) = N_String_Literal
6011 then
6012 raise Not_Handled;
6013 end if;
6015 Val := Expr_Rep_Value (N);
6017 -- Adjust for bias, and strip proper number of bits
6019 if Has_Biased_Representation (Ctyp) then
6020 Val := Val - Expr_Value (Type_Low_Bound (Ctyp));
6021 end if;
6023 return Val mod Uint_2 ** Csiz;
6024 end Get_Component_Val;
6026 -- Here we know we have a one dimensional bit packed array
6028 begin
6029 Get_Index_Bounds (First_Index (Typ), Lo, Hi);
6031 -- Cannot do anything if bounds are dynamic
6033 if not Compile_Time_Known_Value (Lo)
6034 or else
6035 not Compile_Time_Known_Value (Hi)
6036 then
6037 return False;
6038 end if;
6040 -- Or are silly out of range of int bounds
6042 Lob := Expr_Value (Lo);
6043 Hib := Expr_Value (Hi);
6045 if not UI_Is_In_Int_Range (Lob)
6046 or else
6047 not UI_Is_In_Int_Range (Hib)
6048 then
6049 return False;
6050 end if;
6052 -- At this stage we have a suitable aggregate for handling at compile
6053 -- time (the only remaining checks are that the values of expressions
6054 -- in the aggregate are compile time known (check is performed by
6055 -- Get_Component_Val), and that any subtypes or ranges are statically
6056 -- known.
6058 -- If the aggregate is not fully positional at this stage, then
6059 -- convert it to positional form. Either this will fail, in which
6060 -- case we can do nothing, or it will succeed, in which case we have
6061 -- succeeded in handling the aggregate, or it will stay an aggregate,
6062 -- in which case we have failed to handle this case.
6064 if Present (Component_Associations (N)) then
6065 Convert_To_Positional
6066 (N, Max_Others_Replicate => 64, Handle_Bit_Packed => True);
6067 return Nkind (N) /= N_Aggregate;
6068 end if;
6070 -- Otherwise we are all positional, so convert to proper value
6072 declare
6073 Lov : constant Int := UI_To_Int (Lob);
6074 Hiv : constant Int := UI_To_Int (Hib);
6076 Len : constant Nat := Int'Max (0, Hiv - Lov + 1);
6077 -- The length of the array (number of elements)
6079 Aggregate_Val : Uint;
6080 -- Value of aggregate. The value is set in the low order bits of
6081 -- this value. For the little-endian case, the values are stored
6082 -- from low-order to high-order and for the big-endian case the
6083 -- values are stored from high-order to low-order. Note that gigi
6084 -- will take care of the conversions to left justify the value in
6085 -- the big endian case (because of left justified modular type
6086 -- processing), so we do not have to worry about that here.
6088 Lit : Node_Id;
6089 -- Integer literal for resulting constructed value
6091 Shift : Nat;
6092 -- Shift count from low order for next value
6094 Incr : Int;
6095 -- Shift increment for loop
6097 Expr : Node_Id;
6098 -- Next expression from positional parameters of aggregate
6100 begin
6101 -- For little endian, we fill up the low order bits of the target
6102 -- value. For big endian we fill up the high order bits of the
6103 -- target value (which is a left justified modular value).
6105 if Bytes_Big_Endian xor Debug_Flag_8 then
6106 Shift := Csiz * (Len - 1);
6107 Incr := -Csiz;
6108 else
6109 Shift := 0;
6110 Incr := +Csiz;
6111 end if;
6113 -- Loop to set the values
6115 if Len = 0 then
6116 Aggregate_Val := Uint_0;
6117 else
6118 Expr := First (Expressions (N));
6119 Aggregate_Val := Get_Component_Val (Expr) * Uint_2 ** Shift;
6121 for J in 2 .. Len loop
6122 Shift := Shift + Incr;
6123 Next (Expr);
6124 Aggregate_Val :=
6125 Aggregate_Val + Get_Component_Val (Expr) * Uint_2 ** Shift;
6126 end loop;
6127 end if;
6129 -- Now we can rewrite with the proper value
6131 Lit :=
6132 Make_Integer_Literal (Loc,
6133 Intval => Aggregate_Val);
6134 Set_Print_In_Hex (Lit);
6136 -- Construct the expression using this literal. Note that it is
6137 -- important to qualify the literal with its proper modular type
6138 -- since universal integer does not have the required range and
6139 -- also this is a left justified modular type, which is important
6140 -- in the big-endian case.
6142 Rewrite (N,
6143 Unchecked_Convert_To (Typ,
6144 Make_Qualified_Expression (Loc,
6145 Subtype_Mark =>
6146 New_Occurrence_Of (Packed_Array_Type (Typ), Loc),
6147 Expression => Lit)));
6149 Analyze_And_Resolve (N, Typ);
6150 return True;
6151 end;
6152 end;
6154 exception
6155 when Not_Handled =>
6156 return False;
6157 end Packed_Array_Aggregate_Handled;
6159 ----------------------------
6160 -- Has_Mutable_Components --
6161 ----------------------------
6163 function Has_Mutable_Components (Typ : Entity_Id) return Boolean is
6164 Comp : Entity_Id;
6166 begin
6167 Comp := First_Component (Typ);
6168 while Present (Comp) loop
6169 if Is_Record_Type (Etype (Comp))
6170 and then Has_Discriminants (Etype (Comp))
6171 and then not Is_Constrained (Etype (Comp))
6172 then
6173 return True;
6174 end if;
6176 Next_Component (Comp);
6177 end loop;
6179 return False;
6180 end Has_Mutable_Components;
6182 ------------------------------
6183 -- Initialize_Discriminants --
6184 ------------------------------
6186 procedure Initialize_Discriminants (N : Node_Id; Typ : Entity_Id) is
6187 Loc : constant Source_Ptr := Sloc (N);
6188 Bas : constant Entity_Id := Base_Type (Typ);
6189 Par : constant Entity_Id := Etype (Bas);
6190 Decl : constant Node_Id := Parent (Par);
6191 Ref : Node_Id;
6193 begin
6194 if Is_Tagged_Type (Bas)
6195 and then Is_Derived_Type (Bas)
6196 and then Has_Discriminants (Par)
6197 and then Has_Discriminants (Bas)
6198 and then Number_Discriminants (Bas) /= Number_Discriminants (Par)
6199 and then Nkind (Decl) = N_Full_Type_Declaration
6200 and then Nkind (Type_Definition (Decl)) = N_Record_Definition
6201 and then Present
6202 (Variant_Part (Component_List (Type_Definition (Decl))))
6203 and then Nkind (N) /= N_Extension_Aggregate
6204 then
6206 -- Call init proc to set discriminants.
6207 -- There should eventually be a special procedure for this ???
6209 Ref := New_Reference_To (Defining_Identifier (N), Loc);
6210 Insert_Actions_After (N,
6211 Build_Initialization_Call (Sloc (N), Ref, Typ));
6212 end if;
6213 end Initialize_Discriminants;
6215 ----------------
6216 -- Must_Slide --
6217 ----------------
6219 function Must_Slide
6220 (Obj_Type : Entity_Id;
6221 Typ : Entity_Id) return Boolean
6223 L1, L2, H1, H2 : Node_Id;
6224 begin
6225 -- No sliding if the type of the object is not established yet, if it is
6226 -- an unconstrained type whose actual subtype comes from the aggregate,
6227 -- or if the two types are identical.
6229 if not Is_Array_Type (Obj_Type) then
6230 return False;
6232 elsif not Is_Constrained (Obj_Type) then
6233 return False;
6235 elsif Typ = Obj_Type then
6236 return False;
6238 else
6239 -- Sliding can only occur along the first dimension
6241 Get_Index_Bounds (First_Index (Typ), L1, H1);
6242 Get_Index_Bounds (First_Index (Obj_Type), L2, H2);
6244 if not Is_Static_Expression (L1)
6245 or else not Is_Static_Expression (L2)
6246 or else not Is_Static_Expression (H1)
6247 or else not Is_Static_Expression (H2)
6248 then
6249 return False;
6250 else
6251 return Expr_Value (L1) /= Expr_Value (L2)
6252 or else Expr_Value (H1) /= Expr_Value (H2);
6253 end if;
6254 end if;
6255 end Must_Slide;
6257 ---------------------------
6258 -- Safe_Slice_Assignment --
6259 ---------------------------
6261 function Safe_Slice_Assignment (N : Node_Id) return Boolean is
6262 Loc : constant Source_Ptr := Sloc (Parent (N));
6263 Pref : constant Node_Id := Prefix (Name (Parent (N)));
6264 Range_Node : constant Node_Id := Discrete_Range (Name (Parent (N)));
6265 Expr : Node_Id;
6266 L_J : Entity_Id;
6267 L_Iter : Node_Id;
6268 L_Body : Node_Id;
6269 Stat : Node_Id;
6271 begin
6272 -- Generate: for J in Range loop Pref (J) := Expr; end loop;
6274 if Comes_From_Source (N)
6275 and then No (Expressions (N))
6276 and then Nkind (First (Choices (First (Component_Associations (N)))))
6277 = N_Others_Choice
6278 then
6279 Expr :=
6280 Expression (First (Component_Associations (N)));
6281 L_J := Make_Defining_Identifier (Loc, New_Internal_Name ('J'));
6283 L_Iter :=
6284 Make_Iteration_Scheme (Loc,
6285 Loop_Parameter_Specification =>
6286 Make_Loop_Parameter_Specification
6287 (Loc,
6288 Defining_Identifier => L_J,
6289 Discrete_Subtype_Definition => Relocate_Node (Range_Node)));
6291 L_Body :=
6292 Make_Assignment_Statement (Loc,
6293 Name =>
6294 Make_Indexed_Component (Loc,
6295 Prefix => Relocate_Node (Pref),
6296 Expressions => New_List (New_Occurrence_Of (L_J, Loc))),
6297 Expression => Relocate_Node (Expr));
6299 -- Construct the final loop
6301 Stat :=
6302 Make_Implicit_Loop_Statement
6303 (Node => Parent (N),
6304 Identifier => Empty,
6305 Iteration_Scheme => L_Iter,
6306 Statements => New_List (L_Body));
6308 -- Set type of aggregate to be type of lhs in assignment,
6309 -- to suppress redundant length checks.
6311 Set_Etype (N, Etype (Name (Parent (N))));
6313 Rewrite (Parent (N), Stat);
6314 Analyze (Parent (N));
6315 return True;
6317 else
6318 return False;
6319 end if;
6320 end Safe_Slice_Assignment;
6322 ---------------------
6323 -- Sort_Case_Table --
6324 ---------------------
6326 procedure Sort_Case_Table (Case_Table : in out Case_Table_Type) is
6327 L : constant Int := Case_Table'First;
6328 U : constant Int := Case_Table'Last;
6329 K : Int;
6330 J : Int;
6331 T : Case_Bounds;
6333 begin
6334 K := L;
6335 while K /= U loop
6336 T := Case_Table (K + 1);
6338 J := K + 1;
6339 while J /= L
6340 and then Expr_Value (Case_Table (J - 1).Choice_Lo) >
6341 Expr_Value (T.Choice_Lo)
6342 loop
6343 Case_Table (J) := Case_Table (J - 1);
6344 J := J - 1;
6345 end loop;
6347 Case_Table (J) := T;
6348 K := K + 1;
6349 end loop;
6350 end Sort_Case_Table;
6352 ----------------------------
6353 -- Static_Array_Aggregate --
6354 ----------------------------
6356 function Static_Array_Aggregate (N : Node_Id) return Boolean is
6357 Bounds : constant Node_Id := Aggregate_Bounds (N);
6359 Typ : constant Entity_Id := Etype (N);
6360 Comp_Type : constant Entity_Id := Component_Type (Typ);
6361 Agg : Node_Id;
6362 Expr : Node_Id;
6363 Lo : Node_Id;
6364 Hi : Node_Id;
6366 begin
6367 if Is_Tagged_Type (Typ)
6368 or else Is_Controlled (Typ)
6369 or else Is_Packed (Typ)
6370 then
6371 return False;
6372 end if;
6374 if Present (Bounds)
6375 and then Nkind (Bounds) = N_Range
6376 and then Nkind (Low_Bound (Bounds)) = N_Integer_Literal
6377 and then Nkind (High_Bound (Bounds)) = N_Integer_Literal
6378 then
6379 Lo := Low_Bound (Bounds);
6380 Hi := High_Bound (Bounds);
6382 if No (Component_Associations (N)) then
6384 -- Verify that all components are static integers
6386 Expr := First (Expressions (N));
6387 while Present (Expr) loop
6388 if Nkind (Expr) /= N_Integer_Literal then
6389 return False;
6390 end if;
6392 Next (Expr);
6393 end loop;
6395 return True;
6397 else
6398 -- We allow only a single named association, either a static
6399 -- range or an others_clause, with a static expression.
6401 Expr := First (Component_Associations (N));
6403 if Present (Expressions (N)) then
6404 return False;
6406 elsif Present (Next (Expr)) then
6407 return False;
6409 elsif Present (Next (First (Choices (Expr)))) then
6410 return False;
6412 else
6413 -- The aggregate is static if all components are literals, or
6414 -- else all its components are static aggregates for the
6415 -- component type. We also limit the size of a static aggregate
6416 -- to prevent runaway static expressions.
6418 if Is_Array_Type (Comp_Type)
6419 or else Is_Record_Type (Comp_Type)
6420 then
6421 if Nkind (Expression (Expr)) /= N_Aggregate
6422 or else
6423 not Compile_Time_Known_Aggregate (Expression (Expr))
6424 then
6425 return False;
6426 end if;
6428 elsif Nkind (Expression (Expr)) /= N_Integer_Literal then
6429 return False;
6431 elsif not Aggr_Size_OK (N, Typ) then
6432 return False;
6433 end if;
6435 -- Create a positional aggregate with the right number of
6436 -- copies of the expression.
6438 Agg := Make_Aggregate (Sloc (N), New_List, No_List);
6440 for I in UI_To_Int (Intval (Lo)) .. UI_To_Int (Intval (Hi))
6441 loop
6442 Append_To
6443 (Expressions (Agg), New_Copy (Expression (Expr)));
6445 -- The copied expression must be analyzed and resolved.
6446 -- Besides setting the type, this ensures that static
6447 -- expressions are appropriately marked as such.
6449 Analyze_And_Resolve
6450 (Last (Expressions (Agg)), Component_Type (Typ));
6451 end loop;
6453 Set_Aggregate_Bounds (Agg, Bounds);
6454 Set_Etype (Agg, Typ);
6455 Set_Analyzed (Agg);
6456 Rewrite (N, Agg);
6457 Set_Compile_Time_Known_Aggregate (N);
6459 return True;
6460 end if;
6461 end if;
6463 else
6464 return False;
6465 end if;
6466 end Static_Array_Aggregate;
6468 end Exp_Aggr;