* config/rs6000/aix61.h (TARGET_DEFAULT): Add MASK_PPC_GPOPT,
[official-gcc.git] / gcc / ada / exp_aggr.adb
blobbcfca25c6b023f011338d76a8bb6eccf9d3a11af
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-2012, 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_Ch6; use Exp_Ch6;
36 with Exp_Ch7; use Exp_Ch7;
37 with Exp_Ch9; use Exp_Ch9;
38 with Exp_Disp; use Exp_Disp;
39 with Exp_Tss; use Exp_Tss;
40 with Fname; use Fname;
41 with Freeze; use Freeze;
42 with Itypes; use Itypes;
43 with Lib; use Lib;
44 with Namet; use Namet;
45 with Nmake; use Nmake;
46 with Nlists; use Nlists;
47 with Opt; use Opt;
48 with Restrict; use Restrict;
49 with Rident; use Rident;
50 with Rtsfind; use Rtsfind;
51 with Ttypes; use Ttypes;
52 with Sem; use Sem;
53 with Sem_Aggr; use Sem_Aggr;
54 with Sem_Aux; use Sem_Aux;
55 with Sem_Ch3; use Sem_Ch3;
56 with Sem_Eval; use Sem_Eval;
57 with Sem_Res; use Sem_Res;
58 with Sem_Util; use Sem_Util;
59 with Sinfo; use Sinfo;
60 with Snames; use Snames;
61 with Stand; use Stand;
62 with Targparm; use Targparm;
63 with Tbuild; use Tbuild;
64 with Uintp; use Uintp;
66 package body Exp_Aggr is
68 type Case_Bounds is record
69 Choice_Lo : Node_Id;
70 Choice_Hi : Node_Id;
71 Choice_Node : Node_Id;
72 end record;
74 type Case_Table_Type is array (Nat range <>) of Case_Bounds;
75 -- Table type used by Check_Case_Choices procedure
77 function Has_Default_Init_Comps (N : Node_Id) return Boolean;
78 -- N is an aggregate (record or array). Checks the presence of default
79 -- initialization (<>) in any component (Ada 2005: AI-287).
81 function Is_Static_Dispatch_Table_Aggregate (N : Node_Id) return Boolean;
82 -- Returns true if N is an aggregate used to initialize the components
83 -- of an statically allocated dispatch table.
85 function Must_Slide
86 (Obj_Type : Entity_Id;
87 Typ : Entity_Id) return Boolean;
88 -- A static array aggregate in an object declaration can in most cases be
89 -- expanded in place. The one exception is when the aggregate is given
90 -- with component associations that specify different bounds from those of
91 -- the type definition in the object declaration. In this pathological
92 -- case the aggregate must slide, and we must introduce an intermediate
93 -- temporary to hold it.
95 -- The same holds in an assignment to one-dimensional array of arrays,
96 -- when a component may be given with bounds that differ from those of the
97 -- component type.
99 procedure Sort_Case_Table (Case_Table : in out Case_Table_Type);
100 -- Sort the Case Table using the Lower Bound of each Choice as the key.
101 -- A simple insertion sort is used since the number of choices in a case
102 -- statement of variant part will usually be small and probably in near
103 -- sorted order.
105 ------------------------------------------------------
106 -- Local subprograms for Record Aggregate Expansion --
107 ------------------------------------------------------
109 function Build_Record_Aggr_Code
110 (N : Node_Id;
111 Typ : Entity_Id;
112 Lhs : Node_Id) return List_Id;
113 -- N is an N_Aggregate or an N_Extension_Aggregate. Typ is the type of the
114 -- aggregate. Target is an expression containing the location on which the
115 -- component by component assignments will take place. Returns the list of
116 -- assignments plus all other adjustments needed for tagged and controlled
117 -- types.
119 procedure Convert_To_Assignments (N : Node_Id; Typ : Entity_Id);
120 -- N is an N_Aggregate or an N_Extension_Aggregate. Typ is the type of the
121 -- aggregate (which can only be a record type, this procedure is only used
122 -- for record types). Transform the given aggregate into a sequence of
123 -- assignments performed component by component.
125 procedure Expand_Record_Aggregate
126 (N : Node_Id;
127 Orig_Tag : Node_Id := Empty;
128 Parent_Expr : Node_Id := Empty);
129 -- This is the top level procedure for record aggregate expansion.
130 -- Expansion for record aggregates needs expand aggregates for tagged
131 -- record types. Specifically Expand_Record_Aggregate adds the Tag
132 -- field in front of the Component_Association list that was created
133 -- during resolution by Resolve_Record_Aggregate.
135 -- N is the record aggregate node.
136 -- Orig_Tag is the value of the Tag that has to be provided for this
137 -- specific aggregate. It carries the tag corresponding to the type
138 -- of the outermost aggregate during the recursive expansion
139 -- Parent_Expr is the ancestor part of the original extension
140 -- aggregate
142 function Has_Mutable_Components (Typ : Entity_Id) return Boolean;
143 -- Return true if one of the component is of a discriminated type with
144 -- defaults. An aggregate for a type with mutable components must be
145 -- expanded into individual assignments.
147 procedure Initialize_Discriminants (N : Node_Id; Typ : Entity_Id);
148 -- If the type of the aggregate is a type extension with renamed discrimi-
149 -- nants, we must initialize the hidden discriminants of the parent.
150 -- Otherwise, the target object must not be initialized. The discriminants
151 -- are initialized by calling the initialization procedure for the type.
152 -- This is incorrect if the initialization of other components has any
153 -- side effects. We restrict this call to the case where the parent type
154 -- has a variant part, because this is the only case where the hidden
155 -- discriminants are accessed, namely when calling discriminant checking
156 -- functions of the parent type, and when applying a stream attribute to
157 -- an object of the derived type.
159 -----------------------------------------------------
160 -- Local Subprograms for Array Aggregate Expansion --
161 -----------------------------------------------------
163 function Aggr_Size_OK (N : Node_Id; Typ : Entity_Id) return Boolean;
164 -- Very large static aggregates present problems to the back-end, and are
165 -- transformed into assignments and loops. This function verifies that the
166 -- total number of components of an aggregate is acceptable for rewriting
167 -- into a purely positional static form. Aggr_Size_OK must be called before
168 -- calling Flatten.
170 -- This function also detects and warns about one-component aggregates that
171 -- appear in a non-static context. Even if the component value is static,
172 -- such an aggregate must be expanded into an assignment.
174 function Backend_Processing_Possible (N : Node_Id) return Boolean;
175 -- This function checks if array aggregate N can be processed directly
176 -- by the backend. If this is the case True is returned.
178 function Build_Array_Aggr_Code
179 (N : Node_Id;
180 Ctype : Entity_Id;
181 Index : Node_Id;
182 Into : Node_Id;
183 Scalar_Comp : Boolean;
184 Indexes : List_Id := No_List) return List_Id;
185 -- This recursive routine returns a list of statements containing the
186 -- loops and assignments that are needed for the expansion of the array
187 -- aggregate N.
189 -- N is the (sub-)aggregate node to be expanded into code. This node has
190 -- been fully analyzed, and its Etype is properly set.
192 -- Index is the index node corresponding to the array sub-aggregate N
194 -- Into is the target expression into which we are copying the aggregate.
195 -- Note that this node may not have been analyzed yet, and so the Etype
196 -- field may not be set.
198 -- Scalar_Comp is True if the component type of the aggregate is scalar
200 -- Indexes is the current list of expressions used to index the object we
201 -- are writing into.
203 procedure Convert_Array_Aggr_In_Allocator
204 (Decl : Node_Id;
205 Aggr : Node_Id;
206 Target : Node_Id);
207 -- If the aggregate appears within an allocator and can be expanded in
208 -- place, this routine generates the individual assignments to components
209 -- of the designated object. This is an optimization over the general
210 -- case, where a temporary is first created on the stack and then used to
211 -- construct the allocated object on the heap.
213 procedure Convert_To_Positional
214 (N : Node_Id;
215 Max_Others_Replicate : Nat := 5;
216 Handle_Bit_Packed : Boolean := False);
217 -- If possible, convert named notation to positional notation. This
218 -- conversion is possible only in some static cases. If the conversion is
219 -- possible, then N is rewritten with the analyzed converted aggregate.
220 -- The parameter Max_Others_Replicate controls the maximum number of
221 -- values corresponding to an others choice that will be converted to
222 -- positional notation (the default of 5 is the normal limit, and reflects
223 -- the fact that normally the loop is better than a lot of separate
224 -- assignments). Note that this limit gets overridden in any case if
225 -- either of the restrictions No_Elaboration_Code or No_Implicit_Loops is
226 -- set. The parameter Handle_Bit_Packed is usually set False (since we do
227 -- not expect the back end to handle bit packed arrays, so the normal case
228 -- of conversion is pointless), but in the special case of a call from
229 -- Packed_Array_Aggregate_Handled, we set this parameter to True, since
230 -- these are cases we handle in there.
232 -- It would seem worthwhile to have a higher default value for Max_Others_
233 -- replicate, but aggregates in the compiler make this impossible: the
234 -- compiler bootstrap fails if Max_Others_Replicate is greater than 25.
235 -- This is unexpected ???
237 procedure Expand_Array_Aggregate (N : Node_Id);
238 -- This is the top-level routine to perform array aggregate expansion.
239 -- N is the N_Aggregate node to be expanded.
241 function Is_Two_Dim_Packed_Array (Typ : Entity_Id) return Boolean;
243 -- For two-dimensional packed aggregates with constant bounds and constant
244 -- components, it is preferable to pack the inner aggregates because the
245 -- whole matrix can then be presented to the back-end as a one-dimensional
246 -- list of literals. This is much more efficient than expanding into single
247 -- component assignments.
249 function Late_Expansion
250 (N : Node_Id;
251 Typ : Entity_Id;
252 Target : Node_Id) return List_Id;
253 -- This routine implements top-down expansion of nested aggregates. In
254 -- doing so, it avoids the generation of temporaries at each level. N is
255 -- a nested record or array aggregate with the Expansion_Delayed flag.
256 -- Typ is the expected type of the aggregate. Target is a (duplicatable)
257 -- expression that will hold the result of the aggregate expansion.
259 function Make_OK_Assignment_Statement
260 (Sloc : Source_Ptr;
261 Name : Node_Id;
262 Expression : Node_Id) return Node_Id;
263 -- This is like Make_Assignment_Statement, except that Assignment_OK
264 -- is set in the left operand. All assignments built by this unit use
265 -- this routine. This is needed to deal with assignments to initialized
266 -- constants that are done in place.
268 function Number_Of_Choices (N : Node_Id) return Nat;
269 -- Returns the number of discrete choices (not including the others choice
270 -- if present) contained in (sub-)aggregate N.
272 function Packed_Array_Aggregate_Handled (N : Node_Id) return Boolean;
273 -- Given an array aggregate, this function handles the case of a packed
274 -- array aggregate with all constant values, where the aggregate can be
275 -- evaluated at compile time. If this is possible, then N is rewritten
276 -- to be its proper compile time value with all the components properly
277 -- assembled. The expression is analyzed and resolved and True is returned.
278 -- If this transformation is not possible, N is unchanged and False is
279 -- returned.
281 function Safe_Slice_Assignment (N : Node_Id) return Boolean;
282 -- If a slice assignment has an aggregate with a single others_choice,
283 -- the assignment can be done in place even if bounds are not static,
284 -- by converting it into a loop over the discrete range of the slice.
286 function Two_Dim_Packed_Array_Handled (N : Node_Id) return Boolean;
287 -- If the type of the aggregate is a two-dimensional bit_packed array
288 -- it may be transformed into an array of bytes with constant values,
289 -- and presented to the back-end as a static value. The function returns
290 -- false if this transformation cannot be performed. THis is similar to,
291 -- and reuses part of the machinery in Packed_Array_Aggregate_Handled.
293 ------------------
294 -- Aggr_Size_OK --
295 ------------------
297 function Aggr_Size_OK (N : Node_Id; Typ : Entity_Id) return Boolean is
298 Lo : Node_Id;
299 Hi : Node_Id;
300 Indx : Node_Id;
301 Siz : Int;
302 Lov : Uint;
303 Hiv : Uint;
305 -- The following constant determines the maximum size of an array
306 -- aggregate produced by converting named to positional notation (e.g.
307 -- from others clauses). This avoids running away with attempts to
308 -- convert huge aggregates, which hit memory limits in the backend.
310 -- The normal limit is 5000, but we increase this limit to 2**24 (about
311 -- 16 million) if Restrictions (No_Elaboration_Code) or Restrictions
312 -- (No_Implicit_Loops) is specified, since in either case we are at
313 -- risk of declaring the program illegal because of this limit. We also
314 -- increase the limit when Static_Elaboration_Desired, given that this
315 -- means that objects are intended to be placed in data memory.
317 -- We also increase the limit if the aggregate is for a packed two-
318 -- dimensional array, because if components are static it is much more
319 -- efficient to construct a one-dimensional equivalent array with static
320 -- components.
322 Max_Aggr_Size : constant Nat :=
323 5000 + (2 ** 24 - 5000) *
324 Boolean'Pos
325 (Restriction_Active (No_Elaboration_Code)
326 or else
327 Restriction_Active (No_Implicit_Loops)
328 or else
329 Is_Two_Dim_Packed_Array (Typ)
330 or else
331 ((Ekind (Current_Scope) = E_Package
332 and then
333 Static_Elaboration_Desired (Current_Scope))));
335 function Component_Count (T : Entity_Id) return Int;
336 -- The limit is applied to the total number of components that the
337 -- aggregate will have, which is the number of static expressions
338 -- that will appear in the flattened array. This requires a recursive
339 -- computation of the number of scalar components of the structure.
341 ---------------------
342 -- Component_Count --
343 ---------------------
345 function Component_Count (T : Entity_Id) return Int is
346 Res : Int := 0;
347 Comp : Entity_Id;
349 begin
350 if Is_Scalar_Type (T) then
351 return 1;
353 elsif Is_Record_Type (T) then
354 Comp := First_Component (T);
355 while Present (Comp) loop
356 Res := Res + Component_Count (Etype (Comp));
357 Next_Component (Comp);
358 end loop;
360 return Res;
362 elsif Is_Array_Type (T) then
363 declare
364 Lo : constant Node_Id :=
365 Type_Low_Bound (Etype (First_Index (T)));
366 Hi : constant Node_Id :=
367 Type_High_Bound (Etype (First_Index (T)));
369 Siz : constant Int := Component_Count (Component_Type (T));
371 begin
372 if not Compile_Time_Known_Value (Lo)
373 or else not Compile_Time_Known_Value (Hi)
374 then
375 return 0;
376 else
377 return
378 Siz * UI_To_Int (Expr_Value (Hi) - Expr_Value (Lo) + 1);
379 end if;
380 end;
382 else
383 -- Can only be a null for an access type
385 return 1;
386 end if;
387 end Component_Count;
389 -- Start of processing for Aggr_Size_OK
391 begin
392 Siz := Component_Count (Component_Type (Typ));
394 Indx := First_Index (Typ);
395 while Present (Indx) loop
396 Lo := Type_Low_Bound (Etype (Indx));
397 Hi := Type_High_Bound (Etype (Indx));
399 -- Bounds need to be known at compile time
401 if not Compile_Time_Known_Value (Lo)
402 or else not Compile_Time_Known_Value (Hi)
403 then
404 return False;
405 end if;
407 Lov := Expr_Value (Lo);
408 Hiv := Expr_Value (Hi);
410 -- A flat array is always safe
412 if Hiv < Lov then
413 return True;
414 end if;
416 -- One-component aggregates are suspicious, and if the context type
417 -- is an object declaration with non-static bounds it will trip gcc;
418 -- such an aggregate must be expanded into a single assignment.
420 if Hiv = Lov
421 and then Nkind (Parent (N)) = N_Object_Declaration
422 then
423 declare
424 Index_Type : constant Entity_Id :=
425 Etype
426 (First_Index
427 (Etype (Defining_Identifier (Parent (N)))));
428 Indx : Node_Id;
430 begin
431 if not Compile_Time_Known_Value (Type_Low_Bound (Index_Type))
432 or else not Compile_Time_Known_Value
433 (Type_High_Bound (Index_Type))
434 then
435 if Present (Component_Associations (N)) then
436 Indx :=
437 First (Choices (First (Component_Associations (N))));
438 if Is_Entity_Name (Indx)
439 and then not Is_Type (Entity (Indx))
440 then
441 Error_Msg_N
442 ("single component aggregate in non-static context?",
443 Indx);
444 Error_Msg_N ("\maybe subtype name was meant?", Indx);
445 end if;
446 end if;
448 return False;
449 end if;
450 end;
451 end if;
453 declare
454 Rng : constant Uint := Hiv - Lov + 1;
456 begin
457 -- Check if size is too large
459 if not UI_Is_In_Int_Range (Rng) then
460 return False;
461 end if;
463 Siz := Siz * UI_To_Int (Rng);
464 end;
466 if Siz <= 0
467 or else Siz > Max_Aggr_Size
468 then
469 return False;
470 end if;
472 -- Bounds must be in integer range, for later array construction
474 if not UI_Is_In_Int_Range (Lov)
475 or else
476 not UI_Is_In_Int_Range (Hiv)
477 then
478 return False;
479 end if;
481 Next_Index (Indx);
482 end loop;
484 return True;
485 end Aggr_Size_OK;
487 ---------------------------------
488 -- Backend_Processing_Possible --
489 ---------------------------------
491 -- Backend processing by Gigi/gcc is possible only if all the following
492 -- conditions are met:
494 -- 1. N is fully positional
496 -- 2. N is not a bit-packed array aggregate;
498 -- 3. The size of N's array type must be known at compile time. Note
499 -- that this implies that the component size is also known
501 -- 4. The array type of N does not follow the Fortran layout convention
502 -- or if it does it must be 1 dimensional.
504 -- 5. The array component type may not be tagged (which could necessitate
505 -- reassignment of proper tags).
507 -- 6. The array component type must not have unaligned bit components
509 -- 7. None of the components of the aggregate may be bit unaligned
510 -- components.
512 -- 8. There cannot be delayed components, since we do not know enough
513 -- at this stage to know if back end processing is possible.
515 -- 9. There cannot be any discriminated record components, since the
516 -- back end cannot handle this complex case.
518 -- 10. No controlled actions need to be generated for components
520 -- 11. For a VM back end, the array should have no aliased components
522 function Backend_Processing_Possible (N : Node_Id) return Boolean is
523 Typ : constant Entity_Id := Etype (N);
524 -- Typ is the correct constrained array subtype of the aggregate
526 function Component_Check (N : Node_Id; Index : Node_Id) return Boolean;
527 -- This routine checks components of aggregate N, enforcing checks
528 -- 1, 7, 8, and 9. In the multi-dimensional case, these checks are
529 -- performed on subaggregates. The Index value is the current index
530 -- being checked in the multi-dimensional case.
532 ---------------------
533 -- Component_Check --
534 ---------------------
536 function Component_Check (N : Node_Id; Index : Node_Id) return Boolean is
537 Expr : Node_Id;
539 begin
540 -- Checks 1: (no component associations)
542 if Present (Component_Associations (N)) then
543 return False;
544 end if;
546 -- Checks on components
548 -- Recurse to check subaggregates, which may appear in qualified
549 -- expressions. If delayed, the front-end will have to expand.
550 -- If the component is a discriminated record, treat as non-static,
551 -- as the back-end cannot handle this properly.
553 Expr := First (Expressions (N));
554 while Present (Expr) loop
556 -- Checks 8: (no delayed components)
558 if Is_Delayed_Aggregate (Expr) then
559 return False;
560 end if;
562 -- Checks 9: (no discriminated records)
564 if Present (Etype (Expr))
565 and then Is_Record_Type (Etype (Expr))
566 and then Has_Discriminants (Etype (Expr))
567 then
568 return False;
569 end if;
571 -- Checks 7. Component must not be bit aligned component
573 if Possible_Bit_Aligned_Component (Expr) then
574 return False;
575 end if;
577 -- Recursion to following indexes for multiple dimension case
579 if Present (Next_Index (Index))
580 and then not Component_Check (Expr, Next_Index (Index))
581 then
582 return False;
583 end if;
585 -- All checks for that component finished, on to next
587 Next (Expr);
588 end loop;
590 return True;
591 end Component_Check;
593 -- Start of processing for Backend_Processing_Possible
595 begin
596 -- Checks 2 (array not bit packed) and 10 (no controlled actions)
598 if Is_Bit_Packed_Array (Typ) or else Needs_Finalization (Typ) then
599 return False;
600 end if;
602 -- If component is limited, aggregate must be expanded because each
603 -- component assignment must be built in place.
605 if Is_Immutably_Limited_Type (Component_Type (Typ)) then
606 return False;
607 end if;
609 -- Checks 4 (array must not be multi-dimensional Fortran case)
611 if Convention (Typ) = Convention_Fortran
612 and then Number_Dimensions (Typ) > 1
613 then
614 return False;
615 end if;
617 -- Checks 3 (size of array must be known at compile time)
619 if not Size_Known_At_Compile_Time (Typ) then
620 return False;
621 end if;
623 -- Checks on components
625 if not Component_Check (N, First_Index (Typ)) then
626 return False;
627 end if;
629 -- Checks 5 (if the component type is tagged, then we may need to do
630 -- tag adjustments. Perhaps this should be refined to check for any
631 -- component associations that actually need tag adjustment, similar
632 -- to the test in Component_Not_OK_For_Backend for record aggregates
633 -- with tagged components, but not clear whether it's worthwhile ???;
634 -- in the case of the JVM, object tags are handled implicitly)
636 if Is_Tagged_Type (Component_Type (Typ))
637 and then Tagged_Type_Expansion
638 then
639 return False;
640 end if;
642 -- Checks 6 (component type must not have bit aligned components)
644 if Type_May_Have_Bit_Aligned_Components (Component_Type (Typ)) then
645 return False;
646 end if;
648 -- Checks 11: Array aggregates with aliased components are currently
649 -- not well supported by the VM backend; disable temporarily this
650 -- backend processing until it is definitely supported.
652 if VM_Target /= No_VM
653 and then Has_Aliased_Components (Base_Type (Typ))
654 then
655 return False;
656 end if;
658 -- Backend processing is possible
660 Set_Size_Known_At_Compile_Time (Etype (N), True);
661 return True;
662 end Backend_Processing_Possible;
664 ---------------------------
665 -- Build_Array_Aggr_Code --
666 ---------------------------
668 -- The code that we generate from a one dimensional aggregate is
670 -- 1. If the sub-aggregate contains discrete choices we
672 -- (a) Sort the discrete choices
674 -- (b) Otherwise for each discrete choice that specifies a range we
675 -- emit a loop. If a range specifies a maximum of three values, or
676 -- we are dealing with an expression we emit a sequence of
677 -- assignments instead of a loop.
679 -- (c) Generate the remaining loops to cover the others choice if any
681 -- 2. If the aggregate contains positional elements we
683 -- (a) translate the positional elements in a series of assignments
685 -- (b) Generate a final loop to cover the others choice if any.
686 -- Note that this final loop has to be a while loop since the case
688 -- L : Integer := Integer'Last;
689 -- H : Integer := Integer'Last;
690 -- A : array (L .. H) := (1, others =>0);
692 -- cannot be handled by a for loop. Thus for the following
694 -- array (L .. H) := (.. positional elements.., others =>E);
696 -- we always generate something like:
698 -- J : Index_Type := Index_Of_Last_Positional_Element;
699 -- while J < H loop
700 -- J := Index_Base'Succ (J)
701 -- Tmp (J) := E;
702 -- end loop;
704 function Build_Array_Aggr_Code
705 (N : Node_Id;
706 Ctype : Entity_Id;
707 Index : Node_Id;
708 Into : Node_Id;
709 Scalar_Comp : Boolean;
710 Indexes : List_Id := No_List) return List_Id
712 Loc : constant Source_Ptr := Sloc (N);
713 Index_Base : constant Entity_Id := Base_Type (Etype (Index));
714 Index_Base_L : constant Node_Id := Type_Low_Bound (Index_Base);
715 Index_Base_H : constant Node_Id := Type_High_Bound (Index_Base);
717 function Add (Val : Int; To : Node_Id) return Node_Id;
718 -- Returns an expression where Val is added to expression To, unless
719 -- To+Val is provably out of To's base type range. To must be an
720 -- already analyzed expression.
722 function Empty_Range (L, H : Node_Id) return Boolean;
723 -- Returns True if the range defined by L .. H is certainly empty
725 function Equal (L, H : Node_Id) return Boolean;
726 -- Returns True if L = H for sure
728 function Index_Base_Name return Node_Id;
729 -- Returns a new reference to the index type name
731 function Gen_Assign (Ind : Node_Id; Expr : Node_Id) return List_Id;
732 -- Ind must be a side-effect free expression. If the input aggregate
733 -- N to Build_Loop contains no sub-aggregates, then this function
734 -- returns the assignment statement:
736 -- Into (Indexes, Ind) := Expr;
738 -- Otherwise we call Build_Code recursively
740 -- Ada 2005 (AI-287): In case of default initialized component, Expr
741 -- is empty and we generate a call to the corresponding IP subprogram.
743 function Gen_Loop (L, H : Node_Id; Expr : Node_Id) return List_Id;
744 -- Nodes L and H must be side-effect free expressions.
745 -- If the input aggregate N to Build_Loop contains no sub-aggregates,
746 -- This routine returns the for loop statement
748 -- for J in Index_Base'(L) .. Index_Base'(H) loop
749 -- Into (Indexes, J) := Expr;
750 -- end loop;
752 -- Otherwise we call Build_Code recursively.
753 -- As an optimization if the loop covers 3 or less scalar elements we
754 -- generate a sequence of assignments.
756 function Gen_While (L, H : Node_Id; Expr : Node_Id) return List_Id;
757 -- Nodes L and H must be side-effect free expressions.
758 -- If the input aggregate N to Build_Loop contains no sub-aggregates,
759 -- This routine returns the while loop statement
761 -- J : Index_Base := L;
762 -- while J < H loop
763 -- J := Index_Base'Succ (J);
764 -- Into (Indexes, J) := Expr;
765 -- end loop;
767 -- Otherwise we call Build_Code recursively
769 function Local_Compile_Time_Known_Value (E : Node_Id) return Boolean;
770 function Local_Expr_Value (E : Node_Id) return Uint;
771 -- These two Local routines are used to replace the corresponding ones
772 -- in sem_eval because while processing the bounds of an aggregate with
773 -- discrete choices whose index type is an enumeration, we build static
774 -- expressions not recognized by Compile_Time_Known_Value as such since
775 -- they have not yet been analyzed and resolved. All the expressions in
776 -- question are things like Index_Base_Name'Val (Const) which we can
777 -- easily recognize as being constant.
779 ---------
780 -- Add --
781 ---------
783 function Add (Val : Int; To : Node_Id) return Node_Id is
784 Expr_Pos : Node_Id;
785 Expr : Node_Id;
786 To_Pos : Node_Id;
787 U_To : Uint;
788 U_Val : constant Uint := UI_From_Int (Val);
790 begin
791 -- Note: do not try to optimize the case of Val = 0, because
792 -- we need to build a new node with the proper Sloc value anyway.
794 -- First test if we can do constant folding
796 if Local_Compile_Time_Known_Value (To) then
797 U_To := Local_Expr_Value (To) + Val;
799 -- Determine if our constant is outside the range of the index.
800 -- If so return an Empty node. This empty node will be caught
801 -- by Empty_Range below.
803 if Compile_Time_Known_Value (Index_Base_L)
804 and then U_To < Expr_Value (Index_Base_L)
805 then
806 return Empty;
808 elsif Compile_Time_Known_Value (Index_Base_H)
809 and then U_To > Expr_Value (Index_Base_H)
810 then
811 return Empty;
812 end if;
814 Expr_Pos := Make_Integer_Literal (Loc, U_To);
815 Set_Is_Static_Expression (Expr_Pos);
817 if not Is_Enumeration_Type (Index_Base) then
818 Expr := Expr_Pos;
820 -- If we are dealing with enumeration return
821 -- Index_Base'Val (Expr_Pos)
823 else
824 Expr :=
825 Make_Attribute_Reference
826 (Loc,
827 Prefix => Index_Base_Name,
828 Attribute_Name => Name_Val,
829 Expressions => New_List (Expr_Pos));
830 end if;
832 return Expr;
833 end if;
835 -- If we are here no constant folding possible
837 if not Is_Enumeration_Type (Index_Base) then
838 Expr :=
839 Make_Op_Add (Loc,
840 Left_Opnd => Duplicate_Subexpr (To),
841 Right_Opnd => Make_Integer_Literal (Loc, U_Val));
843 -- If we are dealing with enumeration return
844 -- Index_Base'Val (Index_Base'Pos (To) + Val)
846 else
847 To_Pos :=
848 Make_Attribute_Reference
849 (Loc,
850 Prefix => Index_Base_Name,
851 Attribute_Name => Name_Pos,
852 Expressions => New_List (Duplicate_Subexpr (To)));
854 Expr_Pos :=
855 Make_Op_Add (Loc,
856 Left_Opnd => To_Pos,
857 Right_Opnd => Make_Integer_Literal (Loc, U_Val));
859 Expr :=
860 Make_Attribute_Reference
861 (Loc,
862 Prefix => Index_Base_Name,
863 Attribute_Name => Name_Val,
864 Expressions => New_List (Expr_Pos));
865 end if;
867 return Expr;
868 end Add;
870 -----------------
871 -- Empty_Range --
872 -----------------
874 function Empty_Range (L, H : Node_Id) return Boolean is
875 Is_Empty : Boolean := False;
876 Low : Node_Id;
877 High : Node_Id;
879 begin
880 -- First check if L or H were already detected as overflowing the
881 -- index base range type by function Add above. If this is so Add
882 -- returns the empty node.
884 if No (L) or else No (H) then
885 return True;
886 end if;
888 for J in 1 .. 3 loop
889 case J is
891 -- L > H range is empty
893 when 1 =>
894 Low := L;
895 High := H;
897 -- B_L > H range must be empty
899 when 2 =>
900 Low := Index_Base_L;
901 High := H;
903 -- L > B_H range must be empty
905 when 3 =>
906 Low := L;
907 High := Index_Base_H;
908 end case;
910 if Local_Compile_Time_Known_Value (Low)
911 and then Local_Compile_Time_Known_Value (High)
912 then
913 Is_Empty :=
914 UI_Gt (Local_Expr_Value (Low), Local_Expr_Value (High));
915 end if;
917 exit when Is_Empty;
918 end loop;
920 return Is_Empty;
921 end Empty_Range;
923 -----------
924 -- Equal --
925 -----------
927 function Equal (L, H : Node_Id) return Boolean is
928 begin
929 if L = H then
930 return True;
932 elsif Local_Compile_Time_Known_Value (L)
933 and then Local_Compile_Time_Known_Value (H)
934 then
935 return UI_Eq (Local_Expr_Value (L), Local_Expr_Value (H));
936 end if;
938 return False;
939 end Equal;
941 ----------------
942 -- Gen_Assign --
943 ----------------
945 function Gen_Assign (Ind : Node_Id; Expr : Node_Id) return List_Id is
946 L : constant List_Id := New_List;
947 A : Node_Id;
949 New_Indexes : List_Id;
950 Indexed_Comp : Node_Id;
951 Expr_Q : Node_Id;
952 Comp_Type : Entity_Id := Empty;
954 function Add_Loop_Actions (Lis : List_Id) return List_Id;
955 -- Collect insert_actions generated in the construction of a
956 -- loop, and prepend them to the sequence of assignments to
957 -- complete the eventual body of the loop.
959 ----------------------
960 -- Add_Loop_Actions --
961 ----------------------
963 function Add_Loop_Actions (Lis : List_Id) return List_Id is
964 Res : List_Id;
966 begin
967 -- Ada 2005 (AI-287): Do nothing else in case of default
968 -- initialized component.
970 if No (Expr) then
971 return Lis;
973 elsif Nkind (Parent (Expr)) = N_Component_Association
974 and then Present (Loop_Actions (Parent (Expr)))
975 then
976 Append_List (Lis, Loop_Actions (Parent (Expr)));
977 Res := Loop_Actions (Parent (Expr));
978 Set_Loop_Actions (Parent (Expr), No_List);
979 return Res;
981 else
982 return Lis;
983 end if;
984 end Add_Loop_Actions;
986 -- Start of processing for Gen_Assign
988 begin
989 if No (Indexes) then
990 New_Indexes := New_List;
991 else
992 New_Indexes := New_Copy_List_Tree (Indexes);
993 end if;
995 Append_To (New_Indexes, Ind);
997 if Present (Next_Index (Index)) then
998 return
999 Add_Loop_Actions (
1000 Build_Array_Aggr_Code
1001 (N => Expr,
1002 Ctype => Ctype,
1003 Index => Next_Index (Index),
1004 Into => Into,
1005 Scalar_Comp => Scalar_Comp,
1006 Indexes => New_Indexes));
1007 end if;
1009 -- If we get here then we are at a bottom-level (sub-)aggregate
1011 Indexed_Comp :=
1012 Checks_Off
1013 (Make_Indexed_Component (Loc,
1014 Prefix => New_Copy_Tree (Into),
1015 Expressions => New_Indexes));
1017 Set_Assignment_OK (Indexed_Comp);
1019 -- Ada 2005 (AI-287): In case of default initialized component, Expr
1020 -- is not present (and therefore we also initialize Expr_Q to empty).
1022 if No (Expr) then
1023 Expr_Q := Empty;
1024 elsif Nkind (Expr) = N_Qualified_Expression then
1025 Expr_Q := Expression (Expr);
1026 else
1027 Expr_Q := Expr;
1028 end if;
1030 if Present (Etype (N))
1031 and then Etype (N) /= Any_Composite
1032 then
1033 Comp_Type := Component_Type (Etype (N));
1034 pragma Assert (Comp_Type = Ctype); -- AI-287
1036 elsif Present (Next (First (New_Indexes))) then
1038 -- Ada 2005 (AI-287): Do nothing in case of default initialized
1039 -- component because we have received the component type in
1040 -- the formal parameter Ctype.
1042 -- ??? Some assert pragmas have been added to check if this new
1043 -- formal can be used to replace this code in all cases.
1045 if Present (Expr) then
1047 -- This is a multidimensional array. Recover the component
1048 -- type from the outermost aggregate, because subaggregates
1049 -- do not have an assigned type.
1051 declare
1052 P : Node_Id;
1054 begin
1055 P := Parent (Expr);
1056 while Present (P) loop
1057 if Nkind (P) = N_Aggregate
1058 and then Present (Etype (P))
1059 then
1060 Comp_Type := Component_Type (Etype (P));
1061 exit;
1063 else
1064 P := Parent (P);
1065 end if;
1066 end loop;
1068 pragma Assert (Comp_Type = Ctype); -- AI-287
1069 end;
1070 end if;
1071 end if;
1073 -- Ada 2005 (AI-287): We only analyze the expression in case of non-
1074 -- default initialized components (otherwise Expr_Q is not present).
1076 if Present (Expr_Q)
1077 and then Nkind_In (Expr_Q, N_Aggregate, N_Extension_Aggregate)
1078 then
1079 -- At this stage the Expression may not have been analyzed yet
1080 -- because the array aggregate code has not been updated to use
1081 -- the Expansion_Delayed flag and avoid analysis altogether to
1082 -- solve the same problem (see Resolve_Aggr_Expr). So let us do
1083 -- the analysis of non-array aggregates now in order to get the
1084 -- value of Expansion_Delayed flag for the inner aggregate ???
1086 if Present (Comp_Type) and then not Is_Array_Type (Comp_Type) then
1087 Analyze_And_Resolve (Expr_Q, Comp_Type);
1088 end if;
1090 if Is_Delayed_Aggregate (Expr_Q) then
1092 -- This is either a subaggregate of a multidimensional array,
1093 -- or a component of an array type whose component type is
1094 -- also an array. In the latter case, the expression may have
1095 -- component associations that provide different bounds from
1096 -- those of the component type, and sliding must occur. Instead
1097 -- of decomposing the current aggregate assignment, force the
1098 -- re-analysis of the assignment, so that a temporary will be
1099 -- generated in the usual fashion, and sliding will take place.
1101 if Nkind (Parent (N)) = N_Assignment_Statement
1102 and then Is_Array_Type (Comp_Type)
1103 and then Present (Component_Associations (Expr_Q))
1104 and then Must_Slide (Comp_Type, Etype (Expr_Q))
1105 then
1106 Set_Expansion_Delayed (Expr_Q, False);
1107 Set_Analyzed (Expr_Q, False);
1109 else
1110 return
1111 Add_Loop_Actions (
1112 Late_Expansion (Expr_Q, Etype (Expr_Q), Indexed_Comp));
1113 end if;
1114 end if;
1115 end if;
1117 -- Ada 2005 (AI-287): In case of default initialized component, call
1118 -- the initialization subprogram associated with the component type.
1119 -- If the component type is an access type, add an explicit null
1120 -- assignment, because for the back-end there is an initialization
1121 -- present for the whole aggregate, and no default initialization
1122 -- will take place.
1124 -- In addition, if the component type is controlled, we must call
1125 -- its Initialize procedure explicitly, because there is no explicit
1126 -- object creation that will invoke it otherwise.
1128 if No (Expr) then
1129 if Present (Base_Init_Proc (Base_Type (Ctype)))
1130 or else Has_Task (Base_Type (Ctype))
1131 then
1132 Append_List_To (L,
1133 Build_Initialization_Call (Loc,
1134 Id_Ref => Indexed_Comp,
1135 Typ => Ctype,
1136 With_Default_Init => True));
1138 elsif Is_Access_Type (Ctype) then
1139 Append_To (L,
1140 Make_Assignment_Statement (Loc,
1141 Name => Indexed_Comp,
1142 Expression => Make_Null (Loc)));
1143 end if;
1145 if Needs_Finalization (Ctype) then
1146 Append_To (L,
1147 Make_Init_Call (
1148 Obj_Ref => New_Copy_Tree (Indexed_Comp),
1149 Typ => Ctype));
1150 end if;
1152 else
1153 -- Now generate the assignment with no associated controlled
1154 -- actions since the target of the assignment may not have been
1155 -- initialized, it is not possible to Finalize it as expected by
1156 -- normal controlled assignment. The rest of the controlled
1157 -- actions are done manually with the proper finalization list
1158 -- coming from the context.
1160 A :=
1161 Make_OK_Assignment_Statement (Loc,
1162 Name => Indexed_Comp,
1163 Expression => New_Copy_Tree (Expr));
1165 if Present (Comp_Type) and then Needs_Finalization (Comp_Type) then
1166 Set_No_Ctrl_Actions (A);
1168 -- If this is an aggregate for an array of arrays, each
1169 -- sub-aggregate will be expanded as well, and even with
1170 -- No_Ctrl_Actions the assignments of inner components will
1171 -- require attachment in their assignments to temporaries.
1172 -- These temporaries must be finalized for each subaggregate,
1173 -- to prevent multiple attachments of the same temporary
1174 -- location to same finalization chain (and consequently
1175 -- circular lists). To ensure that finalization takes place
1176 -- for each subaggregate we wrap the assignment in a block.
1178 if Is_Array_Type (Comp_Type)
1179 and then Nkind (Expr) = N_Aggregate
1180 then
1181 A :=
1182 Make_Block_Statement (Loc,
1183 Handled_Statement_Sequence =>
1184 Make_Handled_Sequence_Of_Statements (Loc,
1185 Statements => New_List (A)));
1186 end if;
1187 end if;
1189 Append_To (L, A);
1191 -- Adjust the tag if tagged (because of possible view
1192 -- conversions), unless compiling for a VM where
1193 -- tags are implicit.
1195 if Present (Comp_Type)
1196 and then Is_Tagged_Type (Comp_Type)
1197 and then Tagged_Type_Expansion
1198 then
1199 declare
1200 Full_Typ : constant Entity_Id := Underlying_Type (Comp_Type);
1202 begin
1203 A :=
1204 Make_OK_Assignment_Statement (Loc,
1205 Name =>
1206 Make_Selected_Component (Loc,
1207 Prefix => New_Copy_Tree (Indexed_Comp),
1208 Selector_Name =>
1209 New_Reference_To
1210 (First_Tag_Component (Full_Typ), Loc)),
1212 Expression =>
1213 Unchecked_Convert_To (RTE (RE_Tag),
1214 New_Reference_To
1215 (Node (First_Elmt (Access_Disp_Table (Full_Typ))),
1216 Loc)));
1218 Append_To (L, A);
1219 end;
1220 end if;
1222 -- Adjust and attach the component to the proper final list, which
1223 -- can be the controller of the outer record object or the final
1224 -- list associated with the scope.
1226 -- If the component is itself an array of controlled types, whose
1227 -- value is given by a sub-aggregate, then the attach calls have
1228 -- been generated when individual subcomponent are assigned, and
1229 -- must not be done again to prevent malformed finalization chains
1230 -- (see comments above, concerning the creation of a block to hold
1231 -- inner finalization actions).
1233 if Present (Comp_Type)
1234 and then Needs_Finalization (Comp_Type)
1235 and then not Is_Limited_Type (Comp_Type)
1236 and then not
1237 (Is_Array_Type (Comp_Type)
1238 and then Is_Controlled (Component_Type (Comp_Type))
1239 and then Nkind (Expr) = N_Aggregate)
1240 then
1241 Append_To (L,
1242 Make_Adjust_Call (
1243 Obj_Ref => New_Copy_Tree (Indexed_Comp),
1244 Typ => Comp_Type));
1245 end if;
1246 end if;
1248 return Add_Loop_Actions (L);
1249 end Gen_Assign;
1251 --------------
1252 -- Gen_Loop --
1253 --------------
1255 function Gen_Loop (L, H : Node_Id; Expr : Node_Id) return List_Id is
1256 L_J : Node_Id;
1258 L_L : Node_Id;
1259 -- Index_Base'(L)
1261 L_H : Node_Id;
1262 -- Index_Base'(H)
1264 L_Range : Node_Id;
1265 -- Index_Base'(L) .. Index_Base'(H)
1267 L_Iteration_Scheme : Node_Id;
1268 -- L_J in Index_Base'(L) .. Index_Base'(H)
1270 L_Body : List_Id;
1271 -- The statements to execute in the loop
1273 S : constant List_Id := New_List;
1274 -- List of statements
1276 Tcopy : Node_Id;
1277 -- Copy of expression tree, used for checking purposes
1279 begin
1280 -- If loop bounds define an empty range return the null statement
1282 if Empty_Range (L, H) then
1283 Append_To (S, Make_Null_Statement (Loc));
1285 -- Ada 2005 (AI-287): Nothing else need to be done in case of
1286 -- default initialized component.
1288 if No (Expr) then
1289 null;
1291 else
1292 -- The expression must be type-checked even though no component
1293 -- of the aggregate will have this value. This is done only for
1294 -- actual components of the array, not for subaggregates. Do
1295 -- the check on a copy, because the expression may be shared
1296 -- among several choices, some of which might be non-null.
1298 if Present (Etype (N))
1299 and then Is_Array_Type (Etype (N))
1300 and then No (Next_Index (Index))
1301 then
1302 Expander_Mode_Save_And_Set (False);
1303 Tcopy := New_Copy_Tree (Expr);
1304 Set_Parent (Tcopy, N);
1305 Analyze_And_Resolve (Tcopy, Component_Type (Etype (N)));
1306 Expander_Mode_Restore;
1307 end if;
1308 end if;
1310 return S;
1312 -- If loop bounds are the same then generate an assignment
1314 elsif Equal (L, H) then
1315 return Gen_Assign (New_Copy_Tree (L), Expr);
1317 -- If H - L <= 2 then generate a sequence of assignments when we are
1318 -- processing the bottom most aggregate and it contains scalar
1319 -- components.
1321 elsif No (Next_Index (Index))
1322 and then Scalar_Comp
1323 and then Local_Compile_Time_Known_Value (L)
1324 and then Local_Compile_Time_Known_Value (H)
1325 and then Local_Expr_Value (H) - Local_Expr_Value (L) <= 2
1326 then
1328 Append_List_To (S, Gen_Assign (New_Copy_Tree (L), Expr));
1329 Append_List_To (S, Gen_Assign (Add (1, To => L), Expr));
1331 if Local_Expr_Value (H) - Local_Expr_Value (L) = 2 then
1332 Append_List_To (S, Gen_Assign (Add (2, To => L), Expr));
1333 end if;
1335 return S;
1336 end if;
1338 -- Otherwise construct the loop, starting with the loop index L_J
1340 L_J := Make_Temporary (Loc, 'J', L);
1342 -- Construct "L .. H" in Index_Base. We use a qualified expression
1343 -- for the bound to convert to the index base, but we don't need
1344 -- to do that if we already have the base type at hand.
1346 if Etype (L) = Index_Base then
1347 L_L := L;
1348 else
1349 L_L :=
1350 Make_Qualified_Expression (Loc,
1351 Subtype_Mark => Index_Base_Name,
1352 Expression => L);
1353 end if;
1355 if Etype (H) = Index_Base then
1356 L_H := H;
1357 else
1358 L_H :=
1359 Make_Qualified_Expression (Loc,
1360 Subtype_Mark => Index_Base_Name,
1361 Expression => H);
1362 end if;
1364 L_Range :=
1365 Make_Range (Loc,
1366 Low_Bound => L_L,
1367 High_Bound => L_H);
1369 -- Construct "for L_J in Index_Base range L .. H"
1371 L_Iteration_Scheme :=
1372 Make_Iteration_Scheme
1373 (Loc,
1374 Loop_Parameter_Specification =>
1375 Make_Loop_Parameter_Specification
1376 (Loc,
1377 Defining_Identifier => L_J,
1378 Discrete_Subtype_Definition => L_Range));
1380 -- Construct the statements to execute in the loop body
1382 L_Body := Gen_Assign (New_Reference_To (L_J, Loc), Expr);
1384 -- Construct the final loop
1386 Append_To (S, Make_Implicit_Loop_Statement
1387 (Node => N,
1388 Identifier => Empty,
1389 Iteration_Scheme => L_Iteration_Scheme,
1390 Statements => L_Body));
1392 -- A small optimization: if the aggregate is initialized with a box
1393 -- and the component type has no initialization procedure, remove the
1394 -- useless empty loop.
1396 if Nkind (First (S)) = N_Loop_Statement
1397 and then Is_Empty_List (Statements (First (S)))
1398 then
1399 return New_List (Make_Null_Statement (Loc));
1400 else
1401 return S;
1402 end if;
1403 end Gen_Loop;
1405 ---------------
1406 -- Gen_While --
1407 ---------------
1409 -- The code built is
1411 -- W_J : Index_Base := L;
1412 -- while W_J < H loop
1413 -- W_J := Index_Base'Succ (W);
1414 -- L_Body;
1415 -- end loop;
1417 function Gen_While (L, H : Node_Id; Expr : Node_Id) return List_Id is
1418 W_J : Node_Id;
1420 W_Decl : Node_Id;
1421 -- W_J : Base_Type := L;
1423 W_Iteration_Scheme : Node_Id;
1424 -- while W_J < H
1426 W_Index_Succ : Node_Id;
1427 -- Index_Base'Succ (J)
1429 W_Increment : Node_Id;
1430 -- W_J := Index_Base'Succ (W)
1432 W_Body : constant List_Id := New_List;
1433 -- The statements to execute in the loop
1435 S : constant List_Id := New_List;
1436 -- list of statement
1438 begin
1439 -- If loop bounds define an empty range or are equal return null
1441 if Empty_Range (L, H) or else Equal (L, H) then
1442 Append_To (S, Make_Null_Statement (Loc));
1443 return S;
1444 end if;
1446 -- Build the decl of W_J
1448 W_J := Make_Temporary (Loc, 'J', L);
1449 W_Decl :=
1450 Make_Object_Declaration
1451 (Loc,
1452 Defining_Identifier => W_J,
1453 Object_Definition => Index_Base_Name,
1454 Expression => L);
1456 -- Theoretically we should do a New_Copy_Tree (L) here, but we know
1457 -- that in this particular case L is a fresh Expr generated by
1458 -- Add which we are the only ones to use.
1460 Append_To (S, W_Decl);
1462 -- Construct " while W_J < H"
1464 W_Iteration_Scheme :=
1465 Make_Iteration_Scheme
1466 (Loc,
1467 Condition => Make_Op_Lt
1468 (Loc,
1469 Left_Opnd => New_Reference_To (W_J, Loc),
1470 Right_Opnd => New_Copy_Tree (H)));
1472 -- Construct the statements to execute in the loop body
1474 W_Index_Succ :=
1475 Make_Attribute_Reference
1476 (Loc,
1477 Prefix => Index_Base_Name,
1478 Attribute_Name => Name_Succ,
1479 Expressions => New_List (New_Reference_To (W_J, Loc)));
1481 W_Increment :=
1482 Make_OK_Assignment_Statement
1483 (Loc,
1484 Name => New_Reference_To (W_J, Loc),
1485 Expression => W_Index_Succ);
1487 Append_To (W_Body, W_Increment);
1488 Append_List_To (W_Body,
1489 Gen_Assign (New_Reference_To (W_J, Loc), Expr));
1491 -- Construct the final loop
1493 Append_To (S, Make_Implicit_Loop_Statement
1494 (Node => N,
1495 Identifier => Empty,
1496 Iteration_Scheme => W_Iteration_Scheme,
1497 Statements => W_Body));
1499 return S;
1500 end Gen_While;
1502 ---------------------
1503 -- Index_Base_Name --
1504 ---------------------
1506 function Index_Base_Name return Node_Id is
1507 begin
1508 return New_Reference_To (Index_Base, Sloc (N));
1509 end Index_Base_Name;
1511 ------------------------------------
1512 -- Local_Compile_Time_Known_Value --
1513 ------------------------------------
1515 function Local_Compile_Time_Known_Value (E : Node_Id) return Boolean is
1516 begin
1517 return Compile_Time_Known_Value (E)
1518 or else
1519 (Nkind (E) = N_Attribute_Reference
1520 and then Attribute_Name (E) = Name_Val
1521 and then Compile_Time_Known_Value (First (Expressions (E))));
1522 end Local_Compile_Time_Known_Value;
1524 ----------------------
1525 -- Local_Expr_Value --
1526 ----------------------
1528 function Local_Expr_Value (E : Node_Id) return Uint is
1529 begin
1530 if Compile_Time_Known_Value (E) then
1531 return Expr_Value (E);
1532 else
1533 return Expr_Value (First (Expressions (E)));
1534 end if;
1535 end Local_Expr_Value;
1537 -- Build_Array_Aggr_Code Variables
1539 Assoc : Node_Id;
1540 Choice : Node_Id;
1541 Expr : Node_Id;
1542 Typ : Entity_Id;
1544 Others_Expr : Node_Id := Empty;
1545 Others_Box_Present : Boolean := False;
1547 Aggr_L : constant Node_Id := Low_Bound (Aggregate_Bounds (N));
1548 Aggr_H : constant Node_Id := High_Bound (Aggregate_Bounds (N));
1549 -- The aggregate bounds of this specific sub-aggregate. Note that if
1550 -- the code generated by Build_Array_Aggr_Code is executed then these
1551 -- bounds are OK. Otherwise a Constraint_Error would have been raised.
1553 Aggr_Low : constant Node_Id := Duplicate_Subexpr_No_Checks (Aggr_L);
1554 Aggr_High : constant Node_Id := Duplicate_Subexpr_No_Checks (Aggr_H);
1555 -- After Duplicate_Subexpr these are side-effect free
1557 Low : Node_Id;
1558 High : Node_Id;
1560 Nb_Choices : Nat := 0;
1561 Table : Case_Table_Type (1 .. Number_Of_Choices (N));
1562 -- Used to sort all the different choice values
1564 Nb_Elements : Int;
1565 -- Number of elements in the positional aggregate
1567 New_Code : constant List_Id := New_List;
1569 -- Start of processing for Build_Array_Aggr_Code
1571 begin
1572 -- First before we start, a special case. if we have a bit packed
1573 -- array represented as a modular type, then clear the value to
1574 -- zero first, to ensure that unused bits are properly cleared.
1576 Typ := Etype (N);
1578 if Present (Typ)
1579 and then Is_Bit_Packed_Array (Typ)
1580 and then Is_Modular_Integer_Type (Packed_Array_Type (Typ))
1581 then
1582 Append_To (New_Code,
1583 Make_Assignment_Statement (Loc,
1584 Name => New_Copy_Tree (Into),
1585 Expression =>
1586 Unchecked_Convert_To (Typ,
1587 Make_Integer_Literal (Loc, Uint_0))));
1588 end if;
1590 -- If the component type contains tasks, we need to build a Master
1591 -- entity in the current scope, because it will be needed if build-
1592 -- in-place functions are called in the expanded code.
1594 if Nkind (Parent (N)) = N_Object_Declaration
1595 and then Has_Task (Typ)
1596 then
1597 Build_Master_Entity (Defining_Identifier (Parent (N)));
1598 end if;
1600 -- STEP 1: Process component associations
1602 -- For those associations that may generate a loop, initialize
1603 -- Loop_Actions to collect inserted actions that may be crated.
1605 -- Skip this if no component associations
1607 if No (Expressions (N)) then
1609 -- STEP 1 (a): Sort the discrete choices
1611 Assoc := First (Component_Associations (N));
1612 while Present (Assoc) loop
1613 Choice := First (Choices (Assoc));
1614 while Present (Choice) loop
1615 if Nkind (Choice) = N_Others_Choice then
1616 Set_Loop_Actions (Assoc, New_List);
1618 if Box_Present (Assoc) then
1619 Others_Box_Present := True;
1620 else
1621 Others_Expr := Expression (Assoc);
1622 end if;
1623 exit;
1624 end if;
1626 Get_Index_Bounds (Choice, Low, High);
1628 if Low /= High then
1629 Set_Loop_Actions (Assoc, New_List);
1630 end if;
1632 Nb_Choices := Nb_Choices + 1;
1633 if Box_Present (Assoc) then
1634 Table (Nb_Choices) := (Choice_Lo => Low,
1635 Choice_Hi => High,
1636 Choice_Node => Empty);
1637 else
1638 Table (Nb_Choices) := (Choice_Lo => Low,
1639 Choice_Hi => High,
1640 Choice_Node => Expression (Assoc));
1641 end if;
1642 Next (Choice);
1643 end loop;
1645 Next (Assoc);
1646 end loop;
1648 -- If there is more than one set of choices these must be static
1649 -- and we can therefore sort them. Remember that Nb_Choices does not
1650 -- account for an others choice.
1652 if Nb_Choices > 1 then
1653 Sort_Case_Table (Table);
1654 end if;
1656 -- STEP 1 (b): take care of the whole set of discrete choices
1658 for J in 1 .. Nb_Choices loop
1659 Low := Table (J).Choice_Lo;
1660 High := Table (J).Choice_Hi;
1661 Expr := Table (J).Choice_Node;
1662 Append_List (Gen_Loop (Low, High, Expr), To => New_Code);
1663 end loop;
1665 -- STEP 1 (c): generate the remaining loops to cover others choice
1666 -- We don't need to generate loops over empty gaps, but if there is
1667 -- a single empty range we must analyze the expression for semantics
1669 if Present (Others_Expr) or else Others_Box_Present then
1670 declare
1671 First : Boolean := True;
1673 begin
1674 for J in 0 .. Nb_Choices loop
1675 if J = 0 then
1676 Low := Aggr_Low;
1677 else
1678 Low := Add (1, To => Table (J).Choice_Hi);
1679 end if;
1681 if J = Nb_Choices then
1682 High := Aggr_High;
1683 else
1684 High := Add (-1, To => Table (J + 1).Choice_Lo);
1685 end if;
1687 -- If this is an expansion within an init proc, make
1688 -- sure that discriminant references are replaced by
1689 -- the corresponding discriminal.
1691 if Inside_Init_Proc then
1692 if Is_Entity_Name (Low)
1693 and then Ekind (Entity (Low)) = E_Discriminant
1694 then
1695 Set_Entity (Low, Discriminal (Entity (Low)));
1696 end if;
1698 if Is_Entity_Name (High)
1699 and then Ekind (Entity (High)) = E_Discriminant
1700 then
1701 Set_Entity (High, Discriminal (Entity (High)));
1702 end if;
1703 end if;
1705 if First
1706 or else not Empty_Range (Low, High)
1707 then
1708 First := False;
1709 Append_List
1710 (Gen_Loop (Low, High, Others_Expr), To => New_Code);
1711 end if;
1712 end loop;
1713 end;
1714 end if;
1716 -- STEP 2: Process positional components
1718 else
1719 -- STEP 2 (a): Generate the assignments for each positional element
1720 -- Note that here we have to use Aggr_L rather than Aggr_Low because
1721 -- Aggr_L is analyzed and Add wants an analyzed expression.
1723 Expr := First (Expressions (N));
1724 Nb_Elements := -1;
1725 while Present (Expr) loop
1726 Nb_Elements := Nb_Elements + 1;
1727 Append_List (Gen_Assign (Add (Nb_Elements, To => Aggr_L), Expr),
1728 To => New_Code);
1729 Next (Expr);
1730 end loop;
1732 -- STEP 2 (b): Generate final loop if an others choice is present
1733 -- Here Nb_Elements gives the offset of the last positional element.
1735 if Present (Component_Associations (N)) then
1736 Assoc := Last (Component_Associations (N));
1738 -- Ada 2005 (AI-287)
1740 if Box_Present (Assoc) then
1741 Append_List (Gen_While (Add (Nb_Elements, To => Aggr_L),
1742 Aggr_High,
1743 Empty),
1744 To => New_Code);
1745 else
1746 Expr := Expression (Assoc);
1748 Append_List (Gen_While (Add (Nb_Elements, To => Aggr_L),
1749 Aggr_High,
1750 Expr), -- AI-287
1751 To => New_Code);
1752 end if;
1753 end if;
1754 end if;
1756 return New_Code;
1757 end Build_Array_Aggr_Code;
1759 ----------------------------
1760 -- Build_Record_Aggr_Code --
1761 ----------------------------
1763 function Build_Record_Aggr_Code
1764 (N : Node_Id;
1765 Typ : Entity_Id;
1766 Lhs : Node_Id) return List_Id
1768 Loc : constant Source_Ptr := Sloc (N);
1769 L : constant List_Id := New_List;
1770 N_Typ : constant Entity_Id := Etype (N);
1772 Comp : Node_Id;
1773 Instr : Node_Id;
1774 Ref : Node_Id;
1775 Target : Entity_Id;
1776 Comp_Type : Entity_Id;
1777 Selector : Entity_Id;
1778 Comp_Expr : Node_Id;
1779 Expr_Q : Node_Id;
1781 -- If this is an internal aggregate, the External_Final_List is an
1782 -- expression for the controller record of the enclosing type.
1784 -- If the current aggregate has several controlled components, this
1785 -- expression will appear in several calls to attach to the finali-
1786 -- zation list, and it must not be shared.
1788 Ancestor_Is_Expression : Boolean := False;
1789 Ancestor_Is_Subtype_Mark : Boolean := False;
1791 Init_Typ : Entity_Id := Empty;
1793 Finalization_Done : Boolean := False;
1794 -- True if Generate_Finalization_Actions has already been called; calls
1795 -- after the first do nothing.
1797 function Ancestor_Discriminant_Value (Disc : Entity_Id) return Node_Id;
1798 -- Returns the value that the given discriminant of an ancestor type
1799 -- should receive (in the absence of a conflict with the value provided
1800 -- by an ancestor part of an extension aggregate).
1802 procedure Check_Ancestor_Discriminants (Anc_Typ : Entity_Id);
1803 -- Check that each of the discriminant values defined by the ancestor
1804 -- part of an extension aggregate match the corresponding values
1805 -- provided by either an association of the aggregate or by the
1806 -- constraint imposed by a parent type (RM95-4.3.2(8)).
1808 function Compatible_Int_Bounds
1809 (Agg_Bounds : Node_Id;
1810 Typ_Bounds : Node_Id) return Boolean;
1811 -- Return true if Agg_Bounds are equal or within Typ_Bounds. It is
1812 -- assumed that both bounds are integer ranges.
1814 procedure Generate_Finalization_Actions;
1815 -- Deal with the various controlled type data structure initializations
1816 -- (but only if it hasn't been done already).
1818 function Get_Constraint_Association (T : Entity_Id) return Node_Id;
1819 -- Returns the first discriminant association in the constraint
1820 -- associated with T, if any, otherwise returns Empty.
1822 procedure Init_Hidden_Discriminants (Typ : Entity_Id; List : List_Id);
1823 -- If Typ is derived, and constrains discriminants of the parent type,
1824 -- these discriminants are not components of the aggregate, and must be
1825 -- initialized. The assignments are appended to List.
1827 function Is_Int_Range_Bounds (Bounds : Node_Id) return Boolean;
1828 -- Check whether Bounds is a range node and its lower and higher bounds
1829 -- are integers literals.
1831 ---------------------------------
1832 -- Ancestor_Discriminant_Value --
1833 ---------------------------------
1835 function Ancestor_Discriminant_Value (Disc : Entity_Id) return Node_Id is
1836 Assoc : Node_Id;
1837 Assoc_Elmt : Elmt_Id;
1838 Aggr_Comp : Entity_Id;
1839 Corresp_Disc : Entity_Id;
1840 Current_Typ : Entity_Id := Base_Type (Typ);
1841 Parent_Typ : Entity_Id;
1842 Parent_Disc : Entity_Id;
1843 Save_Assoc : Node_Id := Empty;
1845 begin
1846 -- First check any discriminant associations to see if any of them
1847 -- provide a value for the discriminant.
1849 if Present (Discriminant_Specifications (Parent (Current_Typ))) then
1850 Assoc := First (Component_Associations (N));
1851 while Present (Assoc) loop
1852 Aggr_Comp := Entity (First (Choices (Assoc)));
1854 if Ekind (Aggr_Comp) = E_Discriminant then
1855 Save_Assoc := Expression (Assoc);
1857 Corresp_Disc := Corresponding_Discriminant (Aggr_Comp);
1858 while Present (Corresp_Disc) loop
1860 -- If found a corresponding discriminant then return the
1861 -- value given in the aggregate. (Note: this is not
1862 -- correct in the presence of side effects. ???)
1864 if Disc = Corresp_Disc then
1865 return Duplicate_Subexpr (Expression (Assoc));
1866 end if;
1868 Corresp_Disc :=
1869 Corresponding_Discriminant (Corresp_Disc);
1870 end loop;
1871 end if;
1873 Next (Assoc);
1874 end loop;
1875 end if;
1877 -- No match found in aggregate, so chain up parent types to find
1878 -- a constraint that defines the value of the discriminant.
1880 Parent_Typ := Etype (Current_Typ);
1881 while Current_Typ /= Parent_Typ loop
1882 if Has_Discriminants (Parent_Typ)
1883 and then not Has_Unknown_Discriminants (Parent_Typ)
1884 then
1885 Parent_Disc := First_Discriminant (Parent_Typ);
1887 -- We either get the association from the subtype indication
1888 -- of the type definition itself, or from the discriminant
1889 -- constraint associated with the type entity (which is
1890 -- preferable, but it's not always present ???)
1892 if Is_Empty_Elmt_List (
1893 Discriminant_Constraint (Current_Typ))
1894 then
1895 Assoc := Get_Constraint_Association (Current_Typ);
1896 Assoc_Elmt := No_Elmt;
1897 else
1898 Assoc_Elmt :=
1899 First_Elmt (Discriminant_Constraint (Current_Typ));
1900 Assoc := Node (Assoc_Elmt);
1901 end if;
1903 -- Traverse the discriminants of the parent type looking
1904 -- for one that corresponds.
1906 while Present (Parent_Disc) and then Present (Assoc) loop
1907 Corresp_Disc := Parent_Disc;
1908 while Present (Corresp_Disc)
1909 and then Disc /= Corresp_Disc
1910 loop
1911 Corresp_Disc :=
1912 Corresponding_Discriminant (Corresp_Disc);
1913 end loop;
1915 if Disc = Corresp_Disc then
1916 if Nkind (Assoc) = N_Discriminant_Association then
1917 Assoc := Expression (Assoc);
1918 end if;
1920 -- If the located association directly denotes a
1921 -- discriminant, then use the value of a saved
1922 -- association of the aggregate. This is a kludge to
1923 -- handle certain cases involving multiple discriminants
1924 -- mapped to a single discriminant of a descendant. It's
1925 -- not clear how to locate the appropriate discriminant
1926 -- value for such cases. ???
1928 if Is_Entity_Name (Assoc)
1929 and then Ekind (Entity (Assoc)) = E_Discriminant
1930 then
1931 Assoc := Save_Assoc;
1932 end if;
1934 return Duplicate_Subexpr (Assoc);
1935 end if;
1937 Next_Discriminant (Parent_Disc);
1939 if No (Assoc_Elmt) then
1940 Next (Assoc);
1941 else
1942 Next_Elmt (Assoc_Elmt);
1943 if Present (Assoc_Elmt) then
1944 Assoc := Node (Assoc_Elmt);
1945 else
1946 Assoc := Empty;
1947 end if;
1948 end if;
1949 end loop;
1950 end if;
1952 Current_Typ := Parent_Typ;
1953 Parent_Typ := Etype (Current_Typ);
1954 end loop;
1956 -- In some cases there's no ancestor value to locate (such as
1957 -- when an ancestor part given by an expression defines the
1958 -- discriminant value).
1960 return Empty;
1961 end Ancestor_Discriminant_Value;
1963 ----------------------------------
1964 -- Check_Ancestor_Discriminants --
1965 ----------------------------------
1967 procedure Check_Ancestor_Discriminants (Anc_Typ : Entity_Id) is
1968 Discr : Entity_Id;
1969 Disc_Value : Node_Id;
1970 Cond : Node_Id;
1972 begin
1973 Discr := First_Discriminant (Base_Type (Anc_Typ));
1974 while Present (Discr) loop
1975 Disc_Value := Ancestor_Discriminant_Value (Discr);
1977 if Present (Disc_Value) then
1978 Cond := Make_Op_Ne (Loc,
1979 Left_Opnd =>
1980 Make_Selected_Component (Loc,
1981 Prefix => New_Copy_Tree (Target),
1982 Selector_Name => New_Occurrence_Of (Discr, Loc)),
1983 Right_Opnd => Disc_Value);
1985 Append_To (L,
1986 Make_Raise_Constraint_Error (Loc,
1987 Condition => Cond,
1988 Reason => CE_Discriminant_Check_Failed));
1989 end if;
1991 Next_Discriminant (Discr);
1992 end loop;
1993 end Check_Ancestor_Discriminants;
1995 ---------------------------
1996 -- Compatible_Int_Bounds --
1997 ---------------------------
1999 function Compatible_Int_Bounds
2000 (Agg_Bounds : Node_Id;
2001 Typ_Bounds : Node_Id) return Boolean
2003 Agg_Lo : constant Uint := Intval (Low_Bound (Agg_Bounds));
2004 Agg_Hi : constant Uint := Intval (High_Bound (Agg_Bounds));
2005 Typ_Lo : constant Uint := Intval (Low_Bound (Typ_Bounds));
2006 Typ_Hi : constant Uint := Intval (High_Bound (Typ_Bounds));
2007 begin
2008 return Typ_Lo <= Agg_Lo and then Agg_Hi <= Typ_Hi;
2009 end Compatible_Int_Bounds;
2011 --------------------------------
2012 -- Get_Constraint_Association --
2013 --------------------------------
2015 function Get_Constraint_Association (T : Entity_Id) return Node_Id is
2016 Indic : Node_Id;
2017 Typ : Entity_Id;
2019 begin
2020 Typ := T;
2022 -- Handle private types in instances
2024 if In_Instance
2025 and then Is_Private_Type (Typ)
2026 and then Present (Full_View (Typ))
2027 then
2028 Typ := Full_View (Typ);
2029 end if;
2031 Indic := Subtype_Indication (Type_Definition (Parent (Typ)));
2033 -- ??? Also need to cover case of a type mark denoting a subtype
2034 -- with constraint.
2036 if Nkind (Indic) = N_Subtype_Indication
2037 and then Present (Constraint (Indic))
2038 then
2039 return First (Constraints (Constraint (Indic)));
2040 end if;
2042 return Empty;
2043 end Get_Constraint_Association;
2045 -------------------------------
2046 -- Init_Hidden_Discriminants --
2047 -------------------------------
2049 procedure Init_Hidden_Discriminants (Typ : Entity_Id; List : List_Id) is
2050 Btype : Entity_Id;
2051 Parent_Type : Entity_Id;
2052 Disc : Entity_Id;
2053 Discr_Val : Elmt_Id;
2055 begin
2056 Btype := Base_Type (Typ);
2057 while Is_Derived_Type (Btype)
2058 and then Present (Stored_Constraint (Btype))
2059 loop
2060 Parent_Type := Etype (Btype);
2062 Disc := First_Discriminant (Parent_Type);
2063 Discr_Val := First_Elmt (Stored_Constraint (Base_Type (Typ)));
2064 while Present (Discr_Val) loop
2066 -- Only those discriminants of the parent that are not
2067 -- renamed by discriminants of the derived type need to
2068 -- be added explicitly.
2070 if not Is_Entity_Name (Node (Discr_Val))
2071 or else Ekind (Entity (Node (Discr_Val))) /= E_Discriminant
2072 then
2073 Comp_Expr :=
2074 Make_Selected_Component (Loc,
2075 Prefix => New_Copy_Tree (Target),
2076 Selector_Name => New_Occurrence_Of (Disc, Loc));
2078 Instr :=
2079 Make_OK_Assignment_Statement (Loc,
2080 Name => Comp_Expr,
2081 Expression => New_Copy_Tree (Node (Discr_Val)));
2083 Set_No_Ctrl_Actions (Instr);
2084 Append_To (List, Instr);
2085 end if;
2087 Next_Discriminant (Disc);
2088 Next_Elmt (Discr_Val);
2089 end loop;
2091 Btype := Base_Type (Parent_Type);
2092 end loop;
2093 end Init_Hidden_Discriminants;
2095 -------------------------
2096 -- Is_Int_Range_Bounds --
2097 -------------------------
2099 function Is_Int_Range_Bounds (Bounds : Node_Id) return Boolean is
2100 begin
2101 return Nkind (Bounds) = N_Range
2102 and then Nkind (Low_Bound (Bounds)) = N_Integer_Literal
2103 and then Nkind (High_Bound (Bounds)) = N_Integer_Literal;
2104 end Is_Int_Range_Bounds;
2106 -----------------------------------
2107 -- Generate_Finalization_Actions --
2108 -----------------------------------
2110 procedure Generate_Finalization_Actions is
2111 begin
2112 -- Do the work only the first time this is called
2114 if Finalization_Done then
2115 return;
2116 end if;
2118 Finalization_Done := True;
2120 -- Determine the external finalization list. It is either the
2121 -- finalization list of the outer-scope or the one coming from
2122 -- an outer aggregate. When the target is not a temporary, the
2123 -- proper scope is the scope of the target rather than the
2124 -- potentially transient current scope.
2126 if Is_Controlled (Typ)
2127 and then Ancestor_Is_Subtype_Mark
2128 then
2129 Ref := Convert_To (Init_Typ, New_Copy_Tree (Target));
2130 Set_Assignment_OK (Ref);
2132 Append_To (L,
2133 Make_Procedure_Call_Statement (Loc,
2134 Name =>
2135 New_Reference_To
2136 (Find_Prim_Op (Init_Typ, Name_Initialize), Loc),
2137 Parameter_Associations => New_List (New_Copy_Tree (Ref))));
2138 end if;
2139 end Generate_Finalization_Actions;
2141 function Rewrite_Discriminant (Expr : Node_Id) return Traverse_Result;
2142 -- If default expression of a component mentions a discriminant of the
2143 -- type, it must be rewritten as the discriminant of the target object.
2145 function Replace_Type (Expr : Node_Id) return Traverse_Result;
2146 -- If the aggregate contains a self-reference, traverse each expression
2147 -- to replace a possible self-reference with a reference to the proper
2148 -- component of the target of the assignment.
2150 --------------------------
2151 -- Rewrite_Discriminant --
2152 --------------------------
2154 function Rewrite_Discriminant (Expr : Node_Id) return Traverse_Result is
2155 begin
2156 if Is_Entity_Name (Expr)
2157 and then Present (Entity (Expr))
2158 and then Ekind (Entity (Expr)) = E_In_Parameter
2159 and then Present (Discriminal_Link (Entity (Expr)))
2160 and then Scope (Discriminal_Link (Entity (Expr)))
2161 = Base_Type (Etype (N))
2162 then
2163 Rewrite (Expr,
2164 Make_Selected_Component (Loc,
2165 Prefix => New_Copy_Tree (Lhs),
2166 Selector_Name => Make_Identifier (Loc, Chars (Expr))));
2167 end if;
2168 return OK;
2169 end Rewrite_Discriminant;
2171 ------------------
2172 -- Replace_Type --
2173 ------------------
2175 function Replace_Type (Expr : Node_Id) return Traverse_Result is
2176 begin
2177 -- Note regarding the Root_Type test below: Aggregate components for
2178 -- self-referential types include attribute references to the current
2179 -- instance, of the form: Typ'access, etc.. These references are
2180 -- rewritten as references to the target of the aggregate: the
2181 -- left-hand side of an assignment, the entity in a declaration,
2182 -- or a temporary. Without this test, we would improperly extended
2183 -- this rewriting to attribute references whose prefix was not the
2184 -- type of the aggregate.
2186 if Nkind (Expr) = N_Attribute_Reference
2187 and then Is_Entity_Name (Prefix (Expr))
2188 and then Is_Type (Entity (Prefix (Expr)))
2189 and then Root_Type (Etype (N)) = Root_Type (Entity (Prefix (Expr)))
2190 then
2191 if Is_Entity_Name (Lhs) then
2192 Rewrite (Prefix (Expr),
2193 New_Occurrence_Of (Entity (Lhs), Loc));
2195 elsif Nkind (Lhs) = N_Selected_Component then
2196 Rewrite (Expr,
2197 Make_Attribute_Reference (Loc,
2198 Attribute_Name => Name_Unrestricted_Access,
2199 Prefix => New_Copy_Tree (Lhs)));
2200 Set_Analyzed (Parent (Expr), False);
2202 else
2203 Rewrite (Expr,
2204 Make_Attribute_Reference (Loc,
2205 Attribute_Name => Name_Unrestricted_Access,
2206 Prefix => New_Copy_Tree (Lhs)));
2207 Set_Analyzed (Parent (Expr), False);
2208 end if;
2209 end if;
2211 return OK;
2212 end Replace_Type;
2214 procedure Replace_Self_Reference is
2215 new Traverse_Proc (Replace_Type);
2217 procedure Replace_Discriminants is
2218 new Traverse_Proc (Rewrite_Discriminant);
2220 -- Start of processing for Build_Record_Aggr_Code
2222 begin
2223 if Has_Self_Reference (N) then
2224 Replace_Self_Reference (N);
2225 end if;
2227 -- If the target of the aggregate is class-wide, we must convert it
2228 -- to the actual type of the aggregate, so that the proper components
2229 -- are visible. We know already that the types are compatible.
2231 if Present (Etype (Lhs))
2232 and then Is_Class_Wide_Type (Etype (Lhs))
2233 then
2234 Target := Unchecked_Convert_To (Typ, Lhs);
2235 else
2236 Target := Lhs;
2237 end if;
2239 -- Deal with the ancestor part of extension aggregates or with the
2240 -- discriminants of the root type.
2242 if Nkind (N) = N_Extension_Aggregate then
2243 declare
2244 Ancestor : constant Node_Id := Ancestor_Part (N);
2245 Assign : List_Id;
2247 begin
2248 -- If the ancestor part is a subtype mark "T", we generate
2250 -- init-proc (T (tmp)); if T is constrained and
2251 -- init-proc (S (tmp)); where S applies an appropriate
2252 -- constraint if T is unconstrained
2254 if Is_Entity_Name (Ancestor)
2255 and then Is_Type (Entity (Ancestor))
2256 then
2257 Ancestor_Is_Subtype_Mark := True;
2259 if Is_Constrained (Entity (Ancestor)) then
2260 Init_Typ := Entity (Ancestor);
2262 -- For an ancestor part given by an unconstrained type mark,
2263 -- create a subtype constrained by appropriate corresponding
2264 -- discriminant values coming from either associations of the
2265 -- aggregate or a constraint on a parent type. The subtype will
2266 -- be used to generate the correct default value for the
2267 -- ancestor part.
2269 elsif Has_Discriminants (Entity (Ancestor)) then
2270 declare
2271 Anc_Typ : constant Entity_Id := Entity (Ancestor);
2272 Anc_Constr : constant List_Id := New_List;
2273 Discrim : Entity_Id;
2274 Disc_Value : Node_Id;
2275 New_Indic : Node_Id;
2276 Subt_Decl : Node_Id;
2278 begin
2279 Discrim := First_Discriminant (Anc_Typ);
2280 while Present (Discrim) loop
2281 Disc_Value := Ancestor_Discriminant_Value (Discrim);
2282 Append_To (Anc_Constr, Disc_Value);
2283 Next_Discriminant (Discrim);
2284 end loop;
2286 New_Indic :=
2287 Make_Subtype_Indication (Loc,
2288 Subtype_Mark => New_Occurrence_Of (Anc_Typ, Loc),
2289 Constraint =>
2290 Make_Index_Or_Discriminant_Constraint (Loc,
2291 Constraints => Anc_Constr));
2293 Init_Typ := Create_Itype (Ekind (Anc_Typ), N);
2295 Subt_Decl :=
2296 Make_Subtype_Declaration (Loc,
2297 Defining_Identifier => Init_Typ,
2298 Subtype_Indication => New_Indic);
2300 -- Itypes must be analyzed with checks off Declaration
2301 -- must have a parent for proper handling of subsidiary
2302 -- actions.
2304 Set_Parent (Subt_Decl, N);
2305 Analyze (Subt_Decl, Suppress => All_Checks);
2306 end;
2307 end if;
2309 Ref := Convert_To (Init_Typ, New_Copy_Tree (Target));
2310 Set_Assignment_OK (Ref);
2312 if not Is_Interface (Init_Typ) then
2313 Append_List_To (L,
2314 Build_Initialization_Call (Loc,
2315 Id_Ref => Ref,
2316 Typ => Init_Typ,
2317 In_Init_Proc => Within_Init_Proc,
2318 With_Default_Init => Has_Default_Init_Comps (N)
2319 or else
2320 Has_Task (Base_Type (Init_Typ))));
2322 if Is_Constrained (Entity (Ancestor))
2323 and then Has_Discriminants (Entity (Ancestor))
2324 then
2325 Check_Ancestor_Discriminants (Entity (Ancestor));
2326 end if;
2327 end if;
2329 -- Handle calls to C++ constructors
2331 elsif Is_CPP_Constructor_Call (Ancestor) then
2332 Init_Typ := Etype (Ancestor);
2333 Ref := Convert_To (Init_Typ, New_Copy_Tree (Target));
2334 Set_Assignment_OK (Ref);
2336 Append_List_To (L,
2337 Build_Initialization_Call (Loc,
2338 Id_Ref => Ref,
2339 Typ => Init_Typ,
2340 In_Init_Proc => Within_Init_Proc,
2341 With_Default_Init => Has_Default_Init_Comps (N),
2342 Constructor_Ref => Ancestor));
2344 -- Ada 2005 (AI-287): If the ancestor part is an aggregate of
2345 -- limited type, a recursive call expands the ancestor. Note that
2346 -- in the limited case, the ancestor part must be either a
2347 -- function call (possibly qualified, or wrapped in an unchecked
2348 -- conversion) or aggregate (definitely qualified).
2349 -- The ancestor part can also be a function call (that may be
2350 -- transformed into an explicit dereference) or a qualification
2351 -- of one such.
2353 elsif Is_Limited_Type (Etype (Ancestor))
2354 and then Nkind_In (Unqualify (Ancestor), N_Aggregate,
2355 N_Extension_Aggregate)
2356 then
2357 Ancestor_Is_Expression := True;
2359 -- Set up finalization data for enclosing record, because
2360 -- controlled subcomponents of the ancestor part will be
2361 -- attached to it.
2363 Generate_Finalization_Actions;
2365 Append_List_To (L,
2366 Build_Record_Aggr_Code
2367 (N => Unqualify (Ancestor),
2368 Typ => Etype (Unqualify (Ancestor)),
2369 Lhs => Target));
2371 -- If the ancestor part is an expression "E", we generate
2373 -- T (tmp) := E;
2375 -- In Ada 2005, this includes the case of a (possibly qualified)
2376 -- limited function call. The assignment will turn into a
2377 -- build-in-place function call (for further details, see
2378 -- Make_Build_In_Place_Call_In_Assignment).
2380 else
2381 Ancestor_Is_Expression := True;
2382 Init_Typ := Etype (Ancestor);
2384 -- If the ancestor part is an aggregate, force its full
2385 -- expansion, which was delayed.
2387 if Nkind_In (Unqualify (Ancestor), N_Aggregate,
2388 N_Extension_Aggregate)
2389 then
2390 Set_Analyzed (Ancestor, False);
2391 Set_Analyzed (Expression (Ancestor), False);
2392 end if;
2394 Ref := Convert_To (Init_Typ, New_Copy_Tree (Target));
2395 Set_Assignment_OK (Ref);
2397 -- Make the assignment without usual controlled actions since
2398 -- we only want the post adjust but not the pre finalize here
2399 -- Add manual adjust when necessary.
2401 Assign := New_List (
2402 Make_OK_Assignment_Statement (Loc,
2403 Name => Ref,
2404 Expression => Ancestor));
2405 Set_No_Ctrl_Actions (First (Assign));
2407 -- Assign the tag now to make sure that the dispatching call in
2408 -- the subsequent deep_adjust works properly (unless VM_Target,
2409 -- where tags are implicit).
2411 if Tagged_Type_Expansion then
2412 Instr :=
2413 Make_OK_Assignment_Statement (Loc,
2414 Name =>
2415 Make_Selected_Component (Loc,
2416 Prefix => New_Copy_Tree (Target),
2417 Selector_Name =>
2418 New_Reference_To
2419 (First_Tag_Component (Base_Type (Typ)), Loc)),
2421 Expression =>
2422 Unchecked_Convert_To (RTE (RE_Tag),
2423 New_Reference_To
2424 (Node (First_Elmt
2425 (Access_Disp_Table (Base_Type (Typ)))),
2426 Loc)));
2428 Set_Assignment_OK (Name (Instr));
2429 Append_To (Assign, Instr);
2431 -- Ada 2005 (AI-251): If tagged type has progenitors we must
2432 -- also initialize tags of the secondary dispatch tables.
2434 if Has_Interfaces (Base_Type (Typ)) then
2435 Init_Secondary_Tags
2436 (Typ => Base_Type (Typ),
2437 Target => Target,
2438 Stmts_List => Assign);
2439 end if;
2440 end if;
2442 -- Call Adjust manually
2444 if Needs_Finalization (Etype (Ancestor))
2445 and then not Is_Limited_Type (Etype (Ancestor))
2446 then
2447 Append_To (Assign,
2448 Make_Adjust_Call (
2449 Obj_Ref => New_Copy_Tree (Ref),
2450 Typ => Etype (Ancestor)));
2451 end if;
2453 Append_To (L,
2454 Make_Unsuppress_Block (Loc, Name_Discriminant_Check, Assign));
2456 if Has_Discriminants (Init_Typ) then
2457 Check_Ancestor_Discriminants (Init_Typ);
2458 end if;
2459 end if;
2460 end;
2462 -- Generate assignments of hidden assignments. If the base type is an
2463 -- unchecked union, the discriminants are unknown to the back-end and
2464 -- absent from a value of the type, so assignments for them are not
2465 -- emitted.
2467 if Has_Discriminants (Typ)
2468 and then not Is_Unchecked_Union (Base_Type (Typ))
2469 then
2470 Init_Hidden_Discriminants (Typ, L);
2471 end if;
2473 -- Normal case (not an extension aggregate)
2475 else
2476 -- Generate the discriminant expressions, component by component.
2477 -- If the base type is an unchecked union, the discriminants are
2478 -- unknown to the back-end and absent from a value of the type, so
2479 -- assignments for them are not emitted.
2481 if Has_Discriminants (Typ)
2482 and then not Is_Unchecked_Union (Base_Type (Typ))
2483 then
2484 Init_Hidden_Discriminants (Typ, L);
2486 -- Generate discriminant init values for the visible discriminants
2488 declare
2489 Discriminant : Entity_Id;
2490 Discriminant_Value : Node_Id;
2492 begin
2493 Discriminant := First_Stored_Discriminant (Typ);
2494 while Present (Discriminant) loop
2495 Comp_Expr :=
2496 Make_Selected_Component (Loc,
2497 Prefix => New_Copy_Tree (Target),
2498 Selector_Name => New_Occurrence_Of (Discriminant, Loc));
2500 Discriminant_Value :=
2501 Get_Discriminant_Value (
2502 Discriminant,
2503 N_Typ,
2504 Discriminant_Constraint (N_Typ));
2506 Instr :=
2507 Make_OK_Assignment_Statement (Loc,
2508 Name => Comp_Expr,
2509 Expression => New_Copy_Tree (Discriminant_Value));
2511 Set_No_Ctrl_Actions (Instr);
2512 Append_To (L, Instr);
2514 Next_Stored_Discriminant (Discriminant);
2515 end loop;
2516 end;
2517 end if;
2518 end if;
2520 -- For CPP types we generate an implicit call to the C++ default
2521 -- constructor to ensure the proper initialization of the _Tag
2522 -- component.
2524 if Is_CPP_Class (Root_Type (Typ))
2525 and then CPP_Num_Prims (Typ) > 0
2526 then
2527 Invoke_Constructor : declare
2528 CPP_Parent : constant Entity_Id :=
2529 Enclosing_CPP_Parent (Typ);
2531 procedure Invoke_IC_Proc (T : Entity_Id);
2532 -- Recursive routine used to climb to parents. Required because
2533 -- parents must be initialized before descendants to ensure
2534 -- propagation of inherited C++ slots.
2536 --------------------
2537 -- Invoke_IC_Proc --
2538 --------------------
2540 procedure Invoke_IC_Proc (T : Entity_Id) is
2541 begin
2542 -- Avoid generating extra calls. Initialization required
2543 -- only for types defined from the level of derivation of
2544 -- type of the constructor and the type of the aggregate.
2546 if T = CPP_Parent then
2547 return;
2548 end if;
2550 Invoke_IC_Proc (Etype (T));
2552 -- Generate call to the IC routine
2554 if Present (CPP_Init_Proc (T)) then
2555 Append_To (L,
2556 Make_Procedure_Call_Statement (Loc,
2557 New_Reference_To (CPP_Init_Proc (T), Loc)));
2558 end if;
2559 end Invoke_IC_Proc;
2561 -- Start of processing for Invoke_Constructor
2563 begin
2564 -- Implicit invocation of the C++ constructor
2566 if Nkind (N) = N_Aggregate then
2567 Append_To (L,
2568 Make_Procedure_Call_Statement (Loc,
2569 Name =>
2570 New_Reference_To
2571 (Base_Init_Proc (CPP_Parent), Loc),
2572 Parameter_Associations => New_List (
2573 Unchecked_Convert_To (CPP_Parent,
2574 New_Copy_Tree (Lhs)))));
2575 end if;
2577 Invoke_IC_Proc (Typ);
2578 end Invoke_Constructor;
2579 end if;
2581 -- Generate the assignments, component by component
2583 -- tmp.comp1 := Expr1_From_Aggr;
2584 -- tmp.comp2 := Expr2_From_Aggr;
2585 -- ....
2587 Comp := First (Component_Associations (N));
2588 while Present (Comp) loop
2589 Selector := Entity (First (Choices (Comp)));
2591 -- C++ constructors
2593 if Is_CPP_Constructor_Call (Expression (Comp)) then
2594 Append_List_To (L,
2595 Build_Initialization_Call (Loc,
2596 Id_Ref => Make_Selected_Component (Loc,
2597 Prefix => New_Copy_Tree (Target),
2598 Selector_Name =>
2599 New_Occurrence_Of (Selector, Loc)),
2600 Typ => Etype (Selector),
2601 Enclos_Type => Typ,
2602 With_Default_Init => True,
2603 Constructor_Ref => Expression (Comp)));
2605 -- Ada 2005 (AI-287): For each default-initialized component generate
2606 -- a call to the corresponding IP subprogram if available.
2608 elsif Box_Present (Comp)
2609 and then Has_Non_Null_Base_Init_Proc (Etype (Selector))
2610 then
2611 if Ekind (Selector) /= E_Discriminant then
2612 Generate_Finalization_Actions;
2613 end if;
2615 -- Ada 2005 (AI-287): If the component type has tasks then
2616 -- generate the activation chain and master entities (except
2617 -- in case of an allocator because in that case these entities
2618 -- are generated by Build_Task_Allocate_Block_With_Init_Stmts).
2620 declare
2621 Ctype : constant Entity_Id := Etype (Selector);
2622 Inside_Allocator : Boolean := False;
2623 P : Node_Id := Parent (N);
2625 begin
2626 if Is_Task_Type (Ctype) or else Has_Task (Ctype) then
2627 while Present (P) loop
2628 if Nkind (P) = N_Allocator then
2629 Inside_Allocator := True;
2630 exit;
2631 end if;
2633 P := Parent (P);
2634 end loop;
2636 if not Inside_Init_Proc and not Inside_Allocator then
2637 Build_Activation_Chain_Entity (N);
2638 end if;
2639 end if;
2640 end;
2642 Append_List_To (L,
2643 Build_Initialization_Call (Loc,
2644 Id_Ref => Make_Selected_Component (Loc,
2645 Prefix => New_Copy_Tree (Target),
2646 Selector_Name =>
2647 New_Occurrence_Of (Selector, Loc)),
2648 Typ => Etype (Selector),
2649 Enclos_Type => Typ,
2650 With_Default_Init => True));
2652 -- Prepare for component assignment
2654 elsif Ekind (Selector) /= E_Discriminant
2655 or else Nkind (N) = N_Extension_Aggregate
2656 then
2657 -- All the discriminants have now been assigned
2659 -- This is now a good moment to initialize and attach all the
2660 -- controllers. Their position may depend on the discriminants.
2662 if Ekind (Selector) /= E_Discriminant then
2663 Generate_Finalization_Actions;
2664 end if;
2666 Comp_Type := Underlying_Type (Etype (Selector));
2667 Comp_Expr :=
2668 Make_Selected_Component (Loc,
2669 Prefix => New_Copy_Tree (Target),
2670 Selector_Name => New_Occurrence_Of (Selector, Loc));
2672 if Nkind (Expression (Comp)) = N_Qualified_Expression then
2673 Expr_Q := Expression (Expression (Comp));
2674 else
2675 Expr_Q := Expression (Comp);
2676 end if;
2678 -- Now either create the assignment or generate the code for the
2679 -- inner aggregate top-down.
2681 if Is_Delayed_Aggregate (Expr_Q) then
2683 -- We have the following case of aggregate nesting inside
2684 -- an object declaration:
2686 -- type Arr_Typ is array (Integer range <>) of ...;
2688 -- type Rec_Typ (...) is record
2689 -- Obj_Arr_Typ : Arr_Typ (A .. B);
2690 -- end record;
2692 -- Obj_Rec_Typ : Rec_Typ := (...,
2693 -- Obj_Arr_Typ => (X => (...), Y => (...)));
2695 -- The length of the ranges of the aggregate and Obj_Add_Typ
2696 -- are equal (B - A = Y - X), but they do not coincide (X /=
2697 -- A and B /= Y). This case requires array sliding which is
2698 -- performed in the following manner:
2700 -- subtype Arr_Sub is Arr_Typ (X .. Y);
2701 -- Temp : Arr_Sub;
2702 -- Temp (X) := (...);
2703 -- ...
2704 -- Temp (Y) := (...);
2705 -- Obj_Rec_Typ.Obj_Arr_Typ := Temp;
2707 if Ekind (Comp_Type) = E_Array_Subtype
2708 and then Is_Int_Range_Bounds (Aggregate_Bounds (Expr_Q))
2709 and then Is_Int_Range_Bounds (First_Index (Comp_Type))
2710 and then not
2711 Compatible_Int_Bounds
2712 (Agg_Bounds => Aggregate_Bounds (Expr_Q),
2713 Typ_Bounds => First_Index (Comp_Type))
2714 then
2715 -- Create the array subtype with bounds equal to those of
2716 -- the corresponding aggregate.
2718 declare
2719 SubE : constant Entity_Id := Make_Temporary (Loc, 'T');
2721 SubD : constant Node_Id :=
2722 Make_Subtype_Declaration (Loc,
2723 Defining_Identifier => SubE,
2724 Subtype_Indication =>
2725 Make_Subtype_Indication (Loc,
2726 Subtype_Mark =>
2727 New_Reference_To
2728 (Etype (Comp_Type), Loc),
2729 Constraint =>
2730 Make_Index_Or_Discriminant_Constraint
2731 (Loc,
2732 Constraints => New_List (
2733 New_Copy_Tree
2734 (Aggregate_Bounds (Expr_Q))))));
2736 -- Create a temporary array of the above subtype which
2737 -- will be used to capture the aggregate assignments.
2739 TmpE : constant Entity_Id := Make_Temporary (Loc, 'A', N);
2741 TmpD : constant Node_Id :=
2742 Make_Object_Declaration (Loc,
2743 Defining_Identifier => TmpE,
2744 Object_Definition =>
2745 New_Reference_To (SubE, Loc));
2747 begin
2748 Set_No_Initialization (TmpD);
2749 Append_To (L, SubD);
2750 Append_To (L, TmpD);
2752 -- Expand aggregate into assignments to the temp array
2754 Append_List_To (L,
2755 Late_Expansion (Expr_Q, Comp_Type,
2756 New_Reference_To (TmpE, Loc)));
2758 -- Slide
2760 Append_To (L,
2761 Make_Assignment_Statement (Loc,
2762 Name => New_Copy_Tree (Comp_Expr),
2763 Expression => New_Reference_To (TmpE, Loc)));
2764 end;
2766 -- Normal case (sliding not required)
2768 else
2769 Append_List_To (L,
2770 Late_Expansion (Expr_Q, Comp_Type, Comp_Expr));
2771 end if;
2773 -- Expr_Q is not delayed aggregate
2775 else
2776 if Has_Discriminants (Typ) then
2777 Replace_Discriminants (Expr_Q);
2778 end if;
2780 Instr :=
2781 Make_OK_Assignment_Statement (Loc,
2782 Name => Comp_Expr,
2783 Expression => Expr_Q);
2785 Set_No_Ctrl_Actions (Instr);
2786 Append_To (L, Instr);
2788 -- Adjust the tag if tagged (because of possible view
2789 -- conversions), unless compiling for a VM where tags are
2790 -- implicit.
2792 -- tmp.comp._tag := comp_typ'tag;
2794 if Is_Tagged_Type (Comp_Type)
2795 and then Tagged_Type_Expansion
2796 then
2797 Instr :=
2798 Make_OK_Assignment_Statement (Loc,
2799 Name =>
2800 Make_Selected_Component (Loc,
2801 Prefix => New_Copy_Tree (Comp_Expr),
2802 Selector_Name =>
2803 New_Reference_To
2804 (First_Tag_Component (Comp_Type), Loc)),
2806 Expression =>
2807 Unchecked_Convert_To (RTE (RE_Tag),
2808 New_Reference_To
2809 (Node (First_Elmt (Access_Disp_Table (Comp_Type))),
2810 Loc)));
2812 Append_To (L, Instr);
2813 end if;
2815 -- Generate:
2816 -- Adjust (tmp.comp);
2818 if Needs_Finalization (Comp_Type)
2819 and then not Is_Limited_Type (Comp_Type)
2820 then
2821 Append_To (L,
2822 Make_Adjust_Call (
2823 Obj_Ref => New_Copy_Tree (Comp_Expr),
2824 Typ => Comp_Type));
2825 end if;
2826 end if;
2828 -- ???
2830 elsif Ekind (Selector) = E_Discriminant
2831 and then Nkind (N) /= N_Extension_Aggregate
2832 and then Nkind (Parent (N)) = N_Component_Association
2833 and then Is_Constrained (Typ)
2834 then
2835 -- We must check that the discriminant value imposed by the
2836 -- context is the same as the value given in the subaggregate,
2837 -- because after the expansion into assignments there is no
2838 -- record on which to perform a regular discriminant check.
2840 declare
2841 D_Val : Elmt_Id;
2842 Disc : Entity_Id;
2844 begin
2845 D_Val := First_Elmt (Discriminant_Constraint (Typ));
2846 Disc := First_Discriminant (Typ);
2847 while Chars (Disc) /= Chars (Selector) loop
2848 Next_Discriminant (Disc);
2849 Next_Elmt (D_Val);
2850 end loop;
2852 pragma Assert (Present (D_Val));
2854 -- This check cannot performed for components that are
2855 -- constrained by a current instance, because this is not a
2856 -- value that can be compared with the actual constraint.
2858 if Nkind (Node (D_Val)) /= N_Attribute_Reference
2859 or else not Is_Entity_Name (Prefix (Node (D_Val)))
2860 or else not Is_Type (Entity (Prefix (Node (D_Val))))
2861 then
2862 Append_To (L,
2863 Make_Raise_Constraint_Error (Loc,
2864 Condition =>
2865 Make_Op_Ne (Loc,
2866 Left_Opnd => New_Copy_Tree (Node (D_Val)),
2867 Right_Opnd => Expression (Comp)),
2868 Reason => CE_Discriminant_Check_Failed));
2870 else
2871 -- Find self-reference in previous discriminant assignment,
2872 -- and replace with proper expression.
2874 declare
2875 Ass : Node_Id;
2877 begin
2878 Ass := First (L);
2879 while Present (Ass) loop
2880 if Nkind (Ass) = N_Assignment_Statement
2881 and then Nkind (Name (Ass)) = N_Selected_Component
2882 and then Chars (Selector_Name (Name (Ass))) =
2883 Chars (Disc)
2884 then
2885 Set_Expression
2886 (Ass, New_Copy_Tree (Expression (Comp)));
2887 exit;
2888 end if;
2889 Next (Ass);
2890 end loop;
2891 end;
2892 end if;
2893 end;
2894 end if;
2896 Next (Comp);
2897 end loop;
2899 -- If the type is tagged, the tag needs to be initialized (unless
2900 -- compiling for the Java VM where tags are implicit). It is done
2901 -- late in the initialization process because in some cases, we call
2902 -- the init proc of an ancestor which will not leave out the right tag
2904 if Ancestor_Is_Expression then
2905 null;
2907 -- For CPP types we generated a call to the C++ default constructor
2908 -- before the components have been initialized to ensure the proper
2909 -- initialization of the _Tag component (see above).
2911 elsif Is_CPP_Class (Typ) then
2912 null;
2914 elsif Is_Tagged_Type (Typ) and then Tagged_Type_Expansion then
2915 Instr :=
2916 Make_OK_Assignment_Statement (Loc,
2917 Name =>
2918 Make_Selected_Component (Loc,
2919 Prefix => New_Copy_Tree (Target),
2920 Selector_Name =>
2921 New_Reference_To
2922 (First_Tag_Component (Base_Type (Typ)), Loc)),
2924 Expression =>
2925 Unchecked_Convert_To (RTE (RE_Tag),
2926 New_Reference_To
2927 (Node (First_Elmt (Access_Disp_Table (Base_Type (Typ)))),
2928 Loc)));
2930 Append_To (L, Instr);
2932 -- Ada 2005 (AI-251): If the tagged type has been derived from
2933 -- abstract interfaces we must also initialize the tags of the
2934 -- secondary dispatch tables.
2936 if Has_Interfaces (Base_Type (Typ)) then
2937 Init_Secondary_Tags
2938 (Typ => Base_Type (Typ),
2939 Target => Target,
2940 Stmts_List => L);
2941 end if;
2942 end if;
2944 -- If the controllers have not been initialized yet (by lack of non-
2945 -- discriminant components), let's do it now.
2947 Generate_Finalization_Actions;
2949 return L;
2950 end Build_Record_Aggr_Code;
2952 -------------------------------
2953 -- Convert_Aggr_In_Allocator --
2954 -------------------------------
2956 procedure Convert_Aggr_In_Allocator
2957 (Alloc : Node_Id;
2958 Decl : Node_Id;
2959 Aggr : Node_Id)
2961 Loc : constant Source_Ptr := Sloc (Aggr);
2962 Typ : constant Entity_Id := Etype (Aggr);
2963 Temp : constant Entity_Id := Defining_Identifier (Decl);
2965 Occ : constant Node_Id :=
2966 Unchecked_Convert_To (Typ,
2967 Make_Explicit_Dereference (Loc,
2968 New_Reference_To (Temp, Loc)));
2970 begin
2971 if Is_Array_Type (Typ) then
2972 Convert_Array_Aggr_In_Allocator (Decl, Aggr, Occ);
2974 elsif Has_Default_Init_Comps (Aggr) then
2975 declare
2976 L : constant List_Id := New_List;
2977 Init_Stmts : List_Id;
2979 begin
2980 Init_Stmts := Late_Expansion (Aggr, Typ, Occ);
2982 if Has_Task (Typ) then
2983 Build_Task_Allocate_Block_With_Init_Stmts (L, Aggr, Init_Stmts);
2984 Insert_Actions (Alloc, L);
2985 else
2986 Insert_Actions (Alloc, Init_Stmts);
2987 end if;
2988 end;
2990 else
2991 Insert_Actions (Alloc, Late_Expansion (Aggr, Typ, Occ));
2992 end if;
2993 end Convert_Aggr_In_Allocator;
2995 --------------------------------
2996 -- Convert_Aggr_In_Assignment --
2997 --------------------------------
2999 procedure Convert_Aggr_In_Assignment (N : Node_Id) is
3000 Aggr : Node_Id := Expression (N);
3001 Typ : constant Entity_Id := Etype (Aggr);
3002 Occ : constant Node_Id := New_Copy_Tree (Name (N));
3004 begin
3005 if Nkind (Aggr) = N_Qualified_Expression then
3006 Aggr := Expression (Aggr);
3007 end if;
3009 Insert_Actions_After (N, Late_Expansion (Aggr, Typ, Occ));
3010 end Convert_Aggr_In_Assignment;
3012 ---------------------------------
3013 -- Convert_Aggr_In_Object_Decl --
3014 ---------------------------------
3016 procedure Convert_Aggr_In_Object_Decl (N : Node_Id) is
3017 Obj : constant Entity_Id := Defining_Identifier (N);
3018 Aggr : Node_Id := Expression (N);
3019 Loc : constant Source_Ptr := Sloc (Aggr);
3020 Typ : constant Entity_Id := Etype (Aggr);
3021 Occ : constant Node_Id := New_Occurrence_Of (Obj, Loc);
3023 function Discriminants_Ok return Boolean;
3024 -- If the object type is constrained, the discriminants in the
3025 -- aggregate must be checked against the discriminants of the subtype.
3026 -- This cannot be done using Apply_Discriminant_Checks because after
3027 -- expansion there is no aggregate left to check.
3029 ----------------------
3030 -- Discriminants_Ok --
3031 ----------------------
3033 function Discriminants_Ok return Boolean is
3034 Cond : Node_Id := Empty;
3035 Check : Node_Id;
3036 D : Entity_Id;
3037 Disc1 : Elmt_Id;
3038 Disc2 : Elmt_Id;
3039 Val1 : Node_Id;
3040 Val2 : Node_Id;
3042 begin
3043 D := First_Discriminant (Typ);
3044 Disc1 := First_Elmt (Discriminant_Constraint (Typ));
3045 Disc2 := First_Elmt (Discriminant_Constraint (Etype (Obj)));
3046 while Present (Disc1) and then Present (Disc2) loop
3047 Val1 := Node (Disc1);
3048 Val2 := Node (Disc2);
3050 if not Is_OK_Static_Expression (Val1)
3051 or else not Is_OK_Static_Expression (Val2)
3052 then
3053 Check := Make_Op_Ne (Loc,
3054 Left_Opnd => Duplicate_Subexpr (Val1),
3055 Right_Opnd => Duplicate_Subexpr (Val2));
3057 if No (Cond) then
3058 Cond := Check;
3060 else
3061 Cond := Make_Or_Else (Loc,
3062 Left_Opnd => Cond,
3063 Right_Opnd => Check);
3064 end if;
3066 elsif Expr_Value (Val1) /= Expr_Value (Val2) then
3067 Apply_Compile_Time_Constraint_Error (Aggr,
3068 Msg => "incorrect value for discriminant&?",
3069 Reason => CE_Discriminant_Check_Failed,
3070 Ent => D);
3071 return False;
3072 end if;
3074 Next_Discriminant (D);
3075 Next_Elmt (Disc1);
3076 Next_Elmt (Disc2);
3077 end loop;
3079 -- If any discriminant constraint is non-static, emit a check
3081 if Present (Cond) then
3082 Insert_Action (N,
3083 Make_Raise_Constraint_Error (Loc,
3084 Condition => Cond,
3085 Reason => CE_Discriminant_Check_Failed));
3086 end if;
3088 return True;
3089 end Discriminants_Ok;
3091 -- Start of processing for Convert_Aggr_In_Object_Decl
3093 begin
3094 Set_Assignment_OK (Occ);
3096 if Nkind (Aggr) = N_Qualified_Expression then
3097 Aggr := Expression (Aggr);
3098 end if;
3100 if Has_Discriminants (Typ)
3101 and then Typ /= Etype (Obj)
3102 and then Is_Constrained (Etype (Obj))
3103 and then not Discriminants_Ok
3104 then
3105 return;
3106 end if;
3108 -- If the context is an extended return statement, it has its own
3109 -- finalization machinery (i.e. works like a transient scope) and
3110 -- we do not want to create an additional one, because objects on
3111 -- the finalization list of the return must be moved to the caller's
3112 -- finalization list to complete the return.
3114 -- However, if the aggregate is limited, it is built in place, and the
3115 -- controlled components are not assigned to intermediate temporaries
3116 -- so there is no need for a transient scope in this case either.
3118 if Requires_Transient_Scope (Typ)
3119 and then Ekind (Current_Scope) /= E_Return_Statement
3120 and then not Is_Limited_Type (Typ)
3121 then
3122 Establish_Transient_Scope
3123 (Aggr,
3124 Sec_Stack =>
3125 Is_Controlled (Typ) or else Has_Controlled_Component (Typ));
3126 end if;
3128 Insert_Actions_After (N, Late_Expansion (Aggr, Typ, Occ));
3129 Set_No_Initialization (N);
3130 Initialize_Discriminants (N, Typ);
3131 end Convert_Aggr_In_Object_Decl;
3133 -------------------------------------
3134 -- Convert_Array_Aggr_In_Allocator --
3135 -------------------------------------
3137 procedure Convert_Array_Aggr_In_Allocator
3138 (Decl : Node_Id;
3139 Aggr : Node_Id;
3140 Target : Node_Id)
3142 Aggr_Code : List_Id;
3143 Typ : constant Entity_Id := Etype (Aggr);
3144 Ctyp : constant Entity_Id := Component_Type (Typ);
3146 begin
3147 -- The target is an explicit dereference of the allocated object.
3148 -- Generate component assignments to it, as for an aggregate that
3149 -- appears on the right-hand side of an assignment statement.
3151 Aggr_Code :=
3152 Build_Array_Aggr_Code (Aggr,
3153 Ctype => Ctyp,
3154 Index => First_Index (Typ),
3155 Into => Target,
3156 Scalar_Comp => Is_Scalar_Type (Ctyp));
3158 Insert_Actions_After (Decl, Aggr_Code);
3159 end Convert_Array_Aggr_In_Allocator;
3161 ----------------------------
3162 -- Convert_To_Assignments --
3163 ----------------------------
3165 procedure Convert_To_Assignments (N : Node_Id; Typ : Entity_Id) is
3166 Loc : constant Source_Ptr := Sloc (N);
3167 T : Entity_Id;
3168 Temp : Entity_Id;
3170 Instr : Node_Id;
3171 Target_Expr : Node_Id;
3172 Parent_Kind : Node_Kind;
3173 Unc_Decl : Boolean := False;
3174 Parent_Node : Node_Id;
3176 begin
3177 pragma Assert (not Is_Static_Dispatch_Table_Aggregate (N));
3178 pragma Assert (Is_Record_Type (Typ));
3180 Parent_Node := Parent (N);
3181 Parent_Kind := Nkind (Parent_Node);
3183 if Parent_Kind = N_Qualified_Expression then
3185 -- Check if we are in a unconstrained declaration because in this
3186 -- case the current delayed expansion mechanism doesn't work when
3187 -- the declared object size depend on the initializing expr.
3189 begin
3190 Parent_Node := Parent (Parent_Node);
3191 Parent_Kind := Nkind (Parent_Node);
3193 if Parent_Kind = N_Object_Declaration then
3194 Unc_Decl :=
3195 not Is_Entity_Name (Object_Definition (Parent_Node))
3196 or else Has_Discriminants
3197 (Entity (Object_Definition (Parent_Node)))
3198 or else Is_Class_Wide_Type
3199 (Entity (Object_Definition (Parent_Node)));
3200 end if;
3201 end;
3202 end if;
3204 -- Just set the Delay flag in the cases where the transformation will be
3205 -- done top down from above.
3207 if False
3209 -- Internal aggregate (transformed when expanding the parent)
3211 or else Parent_Kind = N_Aggregate
3212 or else Parent_Kind = N_Extension_Aggregate
3213 or else Parent_Kind = N_Component_Association
3215 -- Allocator (see Convert_Aggr_In_Allocator)
3217 or else Parent_Kind = N_Allocator
3219 -- Object declaration (see Convert_Aggr_In_Object_Decl)
3221 or else (Parent_Kind = N_Object_Declaration and then not Unc_Decl)
3223 -- Safe assignment (see Convert_Aggr_Assignments). So far only the
3224 -- assignments in init procs are taken into account.
3226 or else (Parent_Kind = N_Assignment_Statement
3227 and then Inside_Init_Proc)
3229 -- (Ada 2005) An inherently limited type in a return statement,
3230 -- which will be handled in a build-in-place fashion, and may be
3231 -- rewritten as an extended return and have its own finalization
3232 -- machinery. In the case of a simple return, the aggregate needs
3233 -- to be delayed until the scope for the return statement has been
3234 -- created, so that any finalization chain will be associated with
3235 -- that scope. For extended returns, we delay expansion to avoid the
3236 -- creation of an unwanted transient scope that could result in
3237 -- premature finalization of the return object (which is built in
3238 -- in place within the caller's scope).
3240 or else
3241 (Is_Immutably_Limited_Type (Typ)
3242 and then
3243 (Nkind (Parent (Parent_Node)) = N_Extended_Return_Statement
3244 or else Nkind (Parent_Node) = N_Simple_Return_Statement))
3245 then
3246 Set_Expansion_Delayed (N);
3247 return;
3248 end if;
3250 if Requires_Transient_Scope (Typ) then
3251 Establish_Transient_Scope
3252 (N, Sec_Stack =>
3253 Is_Controlled (Typ) or else Has_Controlled_Component (Typ));
3254 end if;
3256 -- If the aggregate is non-limited, create a temporary. If it is limited
3257 -- and the context is an assignment, this is a subaggregate for an
3258 -- enclosing aggregate being expanded. It must be built in place, so use
3259 -- the target of the current assignment.
3261 if Is_Limited_Type (Typ)
3262 and then Nkind (Parent (N)) = N_Assignment_Statement
3263 then
3264 Target_Expr := New_Copy_Tree (Name (Parent (N)));
3265 Insert_Actions (Parent (N),
3266 Build_Record_Aggr_Code (N, Typ, Target_Expr));
3267 Rewrite (Parent (N), Make_Null_Statement (Loc));
3269 else
3270 Temp := Make_Temporary (Loc, 'A', N);
3272 -- If the type inherits unknown discriminants, use the view with
3273 -- known discriminants if available.
3275 if Has_Unknown_Discriminants (Typ)
3276 and then Present (Underlying_Record_View (Typ))
3277 then
3278 T := Underlying_Record_View (Typ);
3279 else
3280 T := Typ;
3281 end if;
3283 Instr :=
3284 Make_Object_Declaration (Loc,
3285 Defining_Identifier => Temp,
3286 Object_Definition => New_Occurrence_Of (T, Loc));
3288 Set_No_Initialization (Instr);
3289 Insert_Action (N, Instr);
3290 Initialize_Discriminants (Instr, T);
3291 Target_Expr := New_Occurrence_Of (Temp, Loc);
3292 Insert_Actions (N, Build_Record_Aggr_Code (N, T, Target_Expr));
3293 Rewrite (N, New_Occurrence_Of (Temp, Loc));
3294 Analyze_And_Resolve (N, T);
3295 end if;
3296 end Convert_To_Assignments;
3298 ---------------------------
3299 -- Convert_To_Positional --
3300 ---------------------------
3302 procedure Convert_To_Positional
3303 (N : Node_Id;
3304 Max_Others_Replicate : Nat := 5;
3305 Handle_Bit_Packed : Boolean := False)
3307 Typ : constant Entity_Id := Etype (N);
3309 Static_Components : Boolean := True;
3311 procedure Check_Static_Components;
3312 -- Check whether all components of the aggregate are compile-time known
3313 -- values, and can be passed as is to the back-end without further
3314 -- expansion.
3316 function Flatten
3317 (N : Node_Id;
3318 Ix : Node_Id;
3319 Ixb : Node_Id) return Boolean;
3320 -- Convert the aggregate into a purely positional form if possible. On
3321 -- entry the bounds of all dimensions are known to be static, and the
3322 -- total number of components is safe enough to expand.
3324 function Is_Flat (N : Node_Id; Dims : Int) return Boolean;
3325 -- Return True iff the array N is flat (which is not trivial in the case
3326 -- of multidimensional aggregates).
3328 -----------------------------
3329 -- Check_Static_Components --
3330 -----------------------------
3332 procedure Check_Static_Components is
3333 Expr : Node_Id;
3335 begin
3336 Static_Components := True;
3338 if Nkind (N) = N_String_Literal then
3339 null;
3341 elsif Present (Expressions (N)) then
3342 Expr := First (Expressions (N));
3343 while Present (Expr) loop
3344 if Nkind (Expr) /= N_Aggregate
3345 or else not Compile_Time_Known_Aggregate (Expr)
3346 or else Expansion_Delayed (Expr)
3347 then
3348 Static_Components := False;
3349 exit;
3350 end if;
3352 Next (Expr);
3353 end loop;
3354 end if;
3356 if Nkind (N) = N_Aggregate
3357 and then Present (Component_Associations (N))
3358 then
3359 Expr := First (Component_Associations (N));
3360 while Present (Expr) loop
3361 if Nkind_In (Expression (Expr), N_Integer_Literal,
3362 N_Real_Literal)
3363 then
3364 null;
3366 elsif Is_Entity_Name (Expression (Expr))
3367 and then Present (Entity (Expression (Expr)))
3368 and then Ekind (Entity (Expression (Expr))) =
3369 E_Enumeration_Literal
3370 then
3371 null;
3373 elsif Nkind (Expression (Expr)) /= N_Aggregate
3374 or else not Compile_Time_Known_Aggregate (Expression (Expr))
3375 or else Expansion_Delayed (Expression (Expr))
3376 then
3377 Static_Components := False;
3378 exit;
3379 end if;
3381 Next (Expr);
3382 end loop;
3383 end if;
3384 end Check_Static_Components;
3386 -------------
3387 -- Flatten --
3388 -------------
3390 function Flatten
3391 (N : Node_Id;
3392 Ix : Node_Id;
3393 Ixb : Node_Id) return Boolean
3395 Loc : constant Source_Ptr := Sloc (N);
3396 Blo : constant Node_Id := Type_Low_Bound (Etype (Ixb));
3397 Lo : constant Node_Id := Type_Low_Bound (Etype (Ix));
3398 Hi : constant Node_Id := Type_High_Bound (Etype (Ix));
3399 Lov : Uint;
3400 Hiv : Uint;
3402 Others_Present : Boolean := False;
3404 begin
3405 if Nkind (Original_Node (N)) = N_String_Literal then
3406 return True;
3407 end if;
3409 if not Compile_Time_Known_Value (Lo)
3410 or else not Compile_Time_Known_Value (Hi)
3411 then
3412 return False;
3413 end if;
3415 Lov := Expr_Value (Lo);
3416 Hiv := Expr_Value (Hi);
3418 -- Check if there is an others choice
3420 if Present (Component_Associations (N)) then
3421 declare
3422 Assoc : Node_Id;
3423 Choice : Node_Id;
3425 begin
3426 Assoc := First (Component_Associations (N));
3427 while Present (Assoc) loop
3429 -- If this is a box association, flattening is in general
3430 -- not possible because at this point we cannot tell if the
3431 -- default is static or even exists.
3433 if Box_Present (Assoc) then
3434 return False;
3435 end if;
3437 Choice := First (Choices (Assoc));
3439 while Present (Choice) loop
3440 if Nkind (Choice) = N_Others_Choice then
3441 Others_Present := True;
3442 end if;
3444 Next (Choice);
3445 end loop;
3447 Next (Assoc);
3448 end loop;
3449 end;
3450 end if;
3452 -- If the low bound is not known at compile time and others is not
3453 -- present we can proceed since the bounds can be obtained from the
3454 -- aggregate.
3456 -- Note: This case is required in VM platforms since their backends
3457 -- normalize array indexes in the range 0 .. N-1. Hence, if we do
3458 -- not flat an array whose bounds cannot be obtained from the type
3459 -- of the index the backend has no way to properly generate the code.
3460 -- See ACATS c460010 for an example.
3462 if Hiv < Lov
3463 or else (not Compile_Time_Known_Value (Blo)
3464 and then Others_Present)
3465 then
3466 return False;
3467 end if;
3469 -- Determine if set of alternatives is suitable for conversion and
3470 -- build an array containing the values in sequence.
3472 declare
3473 Vals : array (UI_To_Int (Lov) .. UI_To_Int (Hiv))
3474 of Node_Id := (others => Empty);
3475 -- The values in the aggregate sorted appropriately
3477 Vlist : List_Id;
3478 -- Same data as Vals in list form
3480 Rep_Count : Nat;
3481 -- Used to validate Max_Others_Replicate limit
3483 Elmt : Node_Id;
3484 Num : Int := UI_To_Int (Lov);
3485 Choice_Index : Int;
3486 Choice : Node_Id;
3487 Lo, Hi : Node_Id;
3489 begin
3490 if Present (Expressions (N)) then
3491 Elmt := First (Expressions (N));
3492 while Present (Elmt) loop
3493 if Nkind (Elmt) = N_Aggregate
3494 and then Present (Next_Index (Ix))
3495 and then
3496 not Flatten (Elmt, Next_Index (Ix), Next_Index (Ixb))
3497 then
3498 return False;
3499 end if;
3501 Vals (Num) := Relocate_Node (Elmt);
3502 Num := Num + 1;
3504 Next (Elmt);
3505 end loop;
3506 end if;
3508 if No (Component_Associations (N)) then
3509 return True;
3510 end if;
3512 Elmt := First (Component_Associations (N));
3514 if Nkind (Expression (Elmt)) = N_Aggregate then
3515 if Present (Next_Index (Ix))
3516 and then
3517 not Flatten
3518 (Expression (Elmt), Next_Index (Ix), Next_Index (Ixb))
3519 then
3520 return False;
3521 end if;
3522 end if;
3524 Component_Loop : while Present (Elmt) loop
3525 Choice := First (Choices (Elmt));
3526 Choice_Loop : while Present (Choice) loop
3528 -- If we have an others choice, fill in the missing elements
3529 -- subject to the limit established by Max_Others_Replicate.
3531 if Nkind (Choice) = N_Others_Choice then
3532 Rep_Count := 0;
3534 for J in Vals'Range loop
3535 if No (Vals (J)) then
3536 Vals (J) := New_Copy_Tree (Expression (Elmt));
3537 Rep_Count := Rep_Count + 1;
3539 -- Check for maximum others replication. Note that
3540 -- we skip this test if either of the restrictions
3541 -- No_Elaboration_Code or No_Implicit_Loops is
3542 -- active, if this is a preelaborable unit or
3543 -- a predefined unit, or if the unit must be
3544 -- placed in data memory. This also ensures that
3545 -- predefined units get the same level of constant
3546 -- folding in Ada 95 and Ada 2005, where their
3547 -- categorization has changed.
3549 declare
3550 P : constant Entity_Id :=
3551 Cunit_Entity (Current_Sem_Unit);
3553 begin
3554 -- Check if duplication OK and if so continue
3555 -- processing.
3557 if Restriction_Active (No_Elaboration_Code)
3558 or else Restriction_Active (No_Implicit_Loops)
3559 or else
3560 (Ekind (Current_Scope) = E_Package
3561 and then
3562 Static_Elaboration_Desired
3563 (Current_Scope))
3564 or else Is_Preelaborated (P)
3565 or else (Ekind (P) = E_Package_Body
3566 and then
3567 Is_Preelaborated (Spec_Entity (P)))
3568 or else
3569 Is_Predefined_File_Name
3570 (Unit_File_Name (Get_Source_Unit (P)))
3571 then
3572 null;
3574 -- If duplication not OK, then we return False
3575 -- if the replication count is too high
3577 elsif Rep_Count > Max_Others_Replicate then
3578 return False;
3580 -- Continue on if duplication not OK, but the
3581 -- replication count is not excessive.
3583 else
3584 null;
3585 end if;
3586 end;
3587 end if;
3588 end loop;
3590 exit Component_Loop;
3592 -- Case of a subtype mark, identifier or expanded name
3594 elsif Is_Entity_Name (Choice)
3595 and then Is_Type (Entity (Choice))
3596 then
3597 Lo := Type_Low_Bound (Etype (Choice));
3598 Hi := Type_High_Bound (Etype (Choice));
3600 -- Case of subtype indication
3602 elsif Nkind (Choice) = N_Subtype_Indication then
3603 Lo := Low_Bound (Range_Expression (Constraint (Choice)));
3604 Hi := High_Bound (Range_Expression (Constraint (Choice)));
3606 -- Case of a range
3608 elsif Nkind (Choice) = N_Range then
3609 Lo := Low_Bound (Choice);
3610 Hi := High_Bound (Choice);
3612 -- Normal subexpression case
3614 else pragma Assert (Nkind (Choice) in N_Subexpr);
3615 if not Compile_Time_Known_Value (Choice) then
3616 return False;
3618 else
3619 Choice_Index := UI_To_Int (Expr_Value (Choice));
3620 if Choice_Index in Vals'Range then
3621 Vals (Choice_Index) :=
3622 New_Copy_Tree (Expression (Elmt));
3623 goto Continue;
3625 else
3626 -- Choice is statically out-of-range, will be
3627 -- rewritten to raise Constraint_Error.
3629 return False;
3630 end if;
3631 end if;
3632 end if;
3634 -- Range cases merge with Lo,Hi set
3636 if not Compile_Time_Known_Value (Lo)
3637 or else
3638 not Compile_Time_Known_Value (Hi)
3639 then
3640 return False;
3641 else
3642 for J in UI_To_Int (Expr_Value (Lo)) ..
3643 UI_To_Int (Expr_Value (Hi))
3644 loop
3645 Vals (J) := New_Copy_Tree (Expression (Elmt));
3646 end loop;
3647 end if;
3649 <<Continue>>
3650 Next (Choice);
3651 end loop Choice_Loop;
3653 Next (Elmt);
3654 end loop Component_Loop;
3656 -- If we get here the conversion is possible
3658 Vlist := New_List;
3659 for J in Vals'Range loop
3660 Append (Vals (J), Vlist);
3661 end loop;
3663 Rewrite (N, Make_Aggregate (Loc, Expressions => Vlist));
3664 Set_Aggregate_Bounds (N, Aggregate_Bounds (Original_Node (N)));
3665 return True;
3666 end;
3667 end Flatten;
3669 -------------
3670 -- Is_Flat --
3671 -------------
3673 function Is_Flat (N : Node_Id; Dims : Int) return Boolean is
3674 Elmt : Node_Id;
3676 begin
3677 if Dims = 0 then
3678 return True;
3680 elsif Nkind (N) = N_Aggregate then
3681 if Present (Component_Associations (N)) then
3682 return False;
3684 else
3685 Elmt := First (Expressions (N));
3686 while Present (Elmt) loop
3687 if not Is_Flat (Elmt, Dims - 1) then
3688 return False;
3689 end if;
3691 Next (Elmt);
3692 end loop;
3694 return True;
3695 end if;
3696 else
3697 return True;
3698 end if;
3699 end Is_Flat;
3701 -- Start of processing for Convert_To_Positional
3703 begin
3704 -- Ada 2005 (AI-287): Do not convert in case of default initialized
3705 -- components because in this case will need to call the corresponding
3706 -- IP procedure.
3708 if Has_Default_Init_Comps (N) then
3709 return;
3710 end if;
3712 if Is_Flat (N, Number_Dimensions (Typ)) then
3713 return;
3714 end if;
3716 if Is_Bit_Packed_Array (Typ)
3717 and then not Handle_Bit_Packed
3718 then
3719 return;
3720 end if;
3722 -- Do not convert to positional if controlled components are involved
3723 -- since these require special processing
3725 if Has_Controlled_Component (Typ) then
3726 return;
3727 end if;
3729 Check_Static_Components;
3731 -- If the size is known, or all the components are static, try to
3732 -- build a fully positional aggregate.
3734 -- The size of the type may not be known for an aggregate with
3735 -- discriminated array components, but if the components are static
3736 -- it is still possible to verify statically that the length is
3737 -- compatible with the upper bound of the type, and therefore it is
3738 -- worth flattening such aggregates as well.
3740 -- For now the back-end expands these aggregates into individual
3741 -- assignments to the target anyway, but it is conceivable that
3742 -- it will eventually be able to treat such aggregates statically???
3744 if Aggr_Size_OK (N, Typ)
3745 and then Flatten (N, First_Index (Typ), First_Index (Base_Type (Typ)))
3746 then
3747 if Static_Components then
3748 Set_Compile_Time_Known_Aggregate (N);
3749 Set_Expansion_Delayed (N, False);
3750 end if;
3752 Analyze_And_Resolve (N, Typ);
3753 end if;
3755 -- Is Static_Eaboration_Desired has been specified, diagnose aggregates
3756 -- that will still require initialization code.
3758 if (Ekind (Current_Scope) = E_Package
3759 and then Static_Elaboration_Desired (Current_Scope))
3760 and then Nkind (Parent (N)) = N_Object_Declaration
3761 then
3762 declare
3763 Expr : Node_Id;
3765 begin
3766 if Nkind (N) = N_Aggregate and then Present (Expressions (N)) then
3767 Expr := First (Expressions (N));
3768 while Present (Expr) loop
3769 if Nkind_In (Expr, N_Integer_Literal, N_Real_Literal)
3770 or else
3771 (Is_Entity_Name (Expr)
3772 and then Ekind (Entity (Expr)) = E_Enumeration_Literal)
3773 then
3774 null;
3776 else
3777 Error_Msg_N
3778 ("non-static object requires elaboration code?", N);
3779 exit;
3780 end if;
3782 Next (Expr);
3783 end loop;
3785 if Present (Component_Associations (N)) then
3786 Error_Msg_N ("object requires elaboration code?", N);
3787 end if;
3788 end if;
3789 end;
3790 end if;
3791 end Convert_To_Positional;
3793 ----------------------------
3794 -- Expand_Array_Aggregate --
3795 ----------------------------
3797 -- Array aggregate expansion proceeds as follows:
3799 -- 1. If requested we generate code to perform all the array aggregate
3800 -- bound checks, specifically
3802 -- (a) Check that the index range defined by aggregate bounds is
3803 -- compatible with corresponding index subtype.
3805 -- (b) If an others choice is present check that no aggregate
3806 -- index is outside the bounds of the index constraint.
3808 -- (c) For multidimensional arrays make sure that all subaggregates
3809 -- corresponding to the same dimension have the same bounds.
3811 -- 2. Check for packed array aggregate which can be converted to a
3812 -- constant so that the aggregate disappeares completely.
3814 -- 3. Check case of nested aggregate. Generally nested aggregates are
3815 -- handled during the processing of the parent aggregate.
3817 -- 4. Check if the aggregate can be statically processed. If this is the
3818 -- case pass it as is to Gigi. Note that a necessary condition for
3819 -- static processing is that the aggregate be fully positional.
3821 -- 5. If in place aggregate expansion is possible (i.e. no need to create
3822 -- a temporary) then mark the aggregate as such and return. Otherwise
3823 -- create a new temporary and generate the appropriate initialization
3824 -- code.
3826 procedure Expand_Array_Aggregate (N : Node_Id) is
3827 Loc : constant Source_Ptr := Sloc (N);
3829 Typ : constant Entity_Id := Etype (N);
3830 Ctyp : constant Entity_Id := Component_Type (Typ);
3831 -- Typ is the correct constrained array subtype of the aggregate
3832 -- Ctyp is the corresponding component type.
3834 Aggr_Dimension : constant Pos := Number_Dimensions (Typ);
3835 -- Number of aggregate index dimensions
3837 Aggr_Low : array (1 .. Aggr_Dimension) of Node_Id;
3838 Aggr_High : array (1 .. Aggr_Dimension) of Node_Id;
3839 -- Low and High bounds of the constraint for each aggregate index
3841 Aggr_Index_Typ : array (1 .. Aggr_Dimension) of Entity_Id;
3842 -- The type of each index
3844 Maybe_In_Place_OK : Boolean;
3845 -- If the type is neither controlled nor packed and the aggregate
3846 -- is the expression in an assignment, assignment in place may be
3847 -- possible, provided other conditions are met on the LHS.
3849 Others_Present : array (1 .. Aggr_Dimension) of Boolean :=
3850 (others => False);
3851 -- If Others_Present (J) is True, then there is an others choice
3852 -- in one of the sub-aggregates of N at dimension J.
3854 procedure Build_Constrained_Type (Positional : Boolean);
3855 -- If the subtype is not static or unconstrained, build a constrained
3856 -- type using the computable sizes of the aggregate and its sub-
3857 -- aggregates.
3859 procedure Check_Bounds (Aggr_Bounds : Node_Id; Index_Bounds : Node_Id);
3860 -- Checks that the bounds of Aggr_Bounds are within the bounds defined
3861 -- by Index_Bounds.
3863 procedure Check_Same_Aggr_Bounds (Sub_Aggr : Node_Id; Dim : Pos);
3864 -- Checks that in a multi-dimensional array aggregate all subaggregates
3865 -- corresponding to the same dimension have the same bounds.
3866 -- Sub_Aggr is an array sub-aggregate. Dim is the dimension
3867 -- corresponding to the sub-aggregate.
3869 procedure Compute_Others_Present (Sub_Aggr : Node_Id; Dim : Pos);
3870 -- Computes the values of array Others_Present. Sub_Aggr is the
3871 -- array sub-aggregate we start the computation from. Dim is the
3872 -- dimension corresponding to the sub-aggregate.
3874 function In_Place_Assign_OK return Boolean;
3875 -- Simple predicate to determine whether an aggregate assignment can
3876 -- be done in place, because none of the new values can depend on the
3877 -- components of the target of the assignment.
3879 procedure Others_Check (Sub_Aggr : Node_Id; Dim : Pos);
3880 -- Checks that if an others choice is present in any sub-aggregate no
3881 -- aggregate index is outside the bounds of the index constraint.
3882 -- Sub_Aggr is an array sub-aggregate. Dim is the dimension
3883 -- corresponding to the sub-aggregate.
3885 function Safe_Left_Hand_Side (N : Node_Id) return Boolean;
3886 -- In addition to Maybe_In_Place_OK, in order for an aggregate to be
3887 -- built directly into the target of the assignment it must be free
3888 -- of side-effects.
3890 ----------------------------
3891 -- Build_Constrained_Type --
3892 ----------------------------
3894 procedure Build_Constrained_Type (Positional : Boolean) is
3895 Loc : constant Source_Ptr := Sloc (N);
3896 Agg_Type : constant Entity_Id := Make_Temporary (Loc, 'A');
3897 Comp : Node_Id;
3898 Decl : Node_Id;
3899 Typ : constant Entity_Id := Etype (N);
3900 Indexes : constant List_Id := New_List;
3901 Num : Int;
3902 Sub_Agg : Node_Id;
3904 begin
3905 -- If the aggregate is purely positional, all its subaggregates
3906 -- have the same size. We collect the dimensions from the first
3907 -- subaggregate at each level.
3909 if Positional then
3910 Sub_Agg := N;
3912 for D in 1 .. Number_Dimensions (Typ) loop
3913 Sub_Agg := First (Expressions (Sub_Agg));
3915 Comp := Sub_Agg;
3916 Num := 0;
3917 while Present (Comp) loop
3918 Num := Num + 1;
3919 Next (Comp);
3920 end loop;
3922 Append_To (Indexes,
3923 Make_Range (Loc,
3924 Low_Bound => Make_Integer_Literal (Loc, 1),
3925 High_Bound => Make_Integer_Literal (Loc, Num)));
3926 end loop;
3928 else
3929 -- We know the aggregate type is unconstrained and the aggregate
3930 -- is not processable by the back end, therefore not necessarily
3931 -- positional. Retrieve each dimension bounds (computed earlier).
3933 for D in 1 .. Number_Dimensions (Typ) loop
3934 Append (
3935 Make_Range (Loc,
3936 Low_Bound => Aggr_Low (D),
3937 High_Bound => Aggr_High (D)),
3938 Indexes);
3939 end loop;
3940 end if;
3942 Decl :=
3943 Make_Full_Type_Declaration (Loc,
3944 Defining_Identifier => Agg_Type,
3945 Type_Definition =>
3946 Make_Constrained_Array_Definition (Loc,
3947 Discrete_Subtype_Definitions => Indexes,
3948 Component_Definition =>
3949 Make_Component_Definition (Loc,
3950 Aliased_Present => False,
3951 Subtype_Indication =>
3952 New_Occurrence_Of (Component_Type (Typ), Loc))));
3954 Insert_Action (N, Decl);
3955 Analyze (Decl);
3956 Set_Etype (N, Agg_Type);
3957 Set_Is_Itype (Agg_Type);
3958 Freeze_Itype (Agg_Type, N);
3959 end Build_Constrained_Type;
3961 ------------------
3962 -- Check_Bounds --
3963 ------------------
3965 procedure Check_Bounds (Aggr_Bounds : Node_Id; Index_Bounds : Node_Id) is
3966 Aggr_Lo : Node_Id;
3967 Aggr_Hi : Node_Id;
3969 Ind_Lo : Node_Id;
3970 Ind_Hi : Node_Id;
3972 Cond : Node_Id := Empty;
3974 begin
3975 Get_Index_Bounds (Aggr_Bounds, Aggr_Lo, Aggr_Hi);
3976 Get_Index_Bounds (Index_Bounds, Ind_Lo, Ind_Hi);
3978 -- Generate the following test:
3980 -- [constraint_error when
3981 -- Aggr_Lo <= Aggr_Hi and then
3982 -- (Aggr_Lo < Ind_Lo or else Aggr_Hi > Ind_Hi)]
3984 -- As an optimization try to see if some tests are trivially vacuous
3985 -- because we are comparing an expression against itself.
3987 if Aggr_Lo = Ind_Lo and then Aggr_Hi = Ind_Hi then
3988 Cond := Empty;
3990 elsif Aggr_Hi = Ind_Hi then
3991 Cond :=
3992 Make_Op_Lt (Loc,
3993 Left_Opnd => Duplicate_Subexpr_Move_Checks (Aggr_Lo),
3994 Right_Opnd => Duplicate_Subexpr_Move_Checks (Ind_Lo));
3996 elsif Aggr_Lo = Ind_Lo then
3997 Cond :=
3998 Make_Op_Gt (Loc,
3999 Left_Opnd => Duplicate_Subexpr_Move_Checks (Aggr_Hi),
4000 Right_Opnd => Duplicate_Subexpr_Move_Checks (Ind_Hi));
4002 else
4003 Cond :=
4004 Make_Or_Else (Loc,
4005 Left_Opnd =>
4006 Make_Op_Lt (Loc,
4007 Left_Opnd => Duplicate_Subexpr_Move_Checks (Aggr_Lo),
4008 Right_Opnd => Duplicate_Subexpr_Move_Checks (Ind_Lo)),
4010 Right_Opnd =>
4011 Make_Op_Gt (Loc,
4012 Left_Opnd => Duplicate_Subexpr (Aggr_Hi),
4013 Right_Opnd => Duplicate_Subexpr (Ind_Hi)));
4014 end if;
4016 if Present (Cond) then
4017 Cond :=
4018 Make_And_Then (Loc,
4019 Left_Opnd =>
4020 Make_Op_Le (Loc,
4021 Left_Opnd => Duplicate_Subexpr_Move_Checks (Aggr_Lo),
4022 Right_Opnd => Duplicate_Subexpr_Move_Checks (Aggr_Hi)),
4024 Right_Opnd => Cond);
4026 Set_Analyzed (Left_Opnd (Left_Opnd (Cond)), False);
4027 Set_Analyzed (Right_Opnd (Left_Opnd (Cond)), False);
4028 Insert_Action (N,
4029 Make_Raise_Constraint_Error (Loc,
4030 Condition => Cond,
4031 Reason => CE_Length_Check_Failed));
4032 end if;
4033 end Check_Bounds;
4035 ----------------------------
4036 -- Check_Same_Aggr_Bounds --
4037 ----------------------------
4039 procedure Check_Same_Aggr_Bounds (Sub_Aggr : Node_Id; Dim : Pos) is
4040 Sub_Lo : constant Node_Id := Low_Bound (Aggregate_Bounds (Sub_Aggr));
4041 Sub_Hi : constant Node_Id := High_Bound (Aggregate_Bounds (Sub_Aggr));
4042 -- The bounds of this specific sub-aggregate
4044 Aggr_Lo : constant Node_Id := Aggr_Low (Dim);
4045 Aggr_Hi : constant Node_Id := Aggr_High (Dim);
4046 -- The bounds of the aggregate for this dimension
4048 Ind_Typ : constant Entity_Id := Aggr_Index_Typ (Dim);
4049 -- The index type for this dimension.xxx
4051 Cond : Node_Id := Empty;
4052 Assoc : Node_Id;
4053 Expr : Node_Id;
4055 begin
4056 -- If index checks are on generate the test
4058 -- [constraint_error when
4059 -- Aggr_Lo /= Sub_Lo or else Aggr_Hi /= Sub_Hi]
4061 -- As an optimization try to see if some tests are trivially vacuos
4062 -- because we are comparing an expression against itself. Also for
4063 -- the first dimension the test is trivially vacuous because there
4064 -- is just one aggregate for dimension 1.
4066 if Index_Checks_Suppressed (Ind_Typ) then
4067 Cond := Empty;
4069 elsif Dim = 1
4070 or else (Aggr_Lo = Sub_Lo and then Aggr_Hi = Sub_Hi)
4071 then
4072 Cond := Empty;
4074 elsif Aggr_Hi = Sub_Hi then
4075 Cond :=
4076 Make_Op_Ne (Loc,
4077 Left_Opnd => Duplicate_Subexpr_Move_Checks (Aggr_Lo),
4078 Right_Opnd => Duplicate_Subexpr_Move_Checks (Sub_Lo));
4080 elsif Aggr_Lo = Sub_Lo then
4081 Cond :=
4082 Make_Op_Ne (Loc,
4083 Left_Opnd => Duplicate_Subexpr_Move_Checks (Aggr_Hi),
4084 Right_Opnd => Duplicate_Subexpr_Move_Checks (Sub_Hi));
4086 else
4087 Cond :=
4088 Make_Or_Else (Loc,
4089 Left_Opnd =>
4090 Make_Op_Ne (Loc,
4091 Left_Opnd => Duplicate_Subexpr_Move_Checks (Aggr_Lo),
4092 Right_Opnd => Duplicate_Subexpr_Move_Checks (Sub_Lo)),
4094 Right_Opnd =>
4095 Make_Op_Ne (Loc,
4096 Left_Opnd => Duplicate_Subexpr (Aggr_Hi),
4097 Right_Opnd => Duplicate_Subexpr (Sub_Hi)));
4098 end if;
4100 if Present (Cond) then
4101 Insert_Action (N,
4102 Make_Raise_Constraint_Error (Loc,
4103 Condition => Cond,
4104 Reason => CE_Length_Check_Failed));
4105 end if;
4107 -- Now look inside the sub-aggregate to see if there is more work
4109 if Dim < Aggr_Dimension then
4111 -- Process positional components
4113 if Present (Expressions (Sub_Aggr)) then
4114 Expr := First (Expressions (Sub_Aggr));
4115 while Present (Expr) loop
4116 Check_Same_Aggr_Bounds (Expr, Dim + 1);
4117 Next (Expr);
4118 end loop;
4119 end if;
4121 -- Process component associations
4123 if Present (Component_Associations (Sub_Aggr)) then
4124 Assoc := First (Component_Associations (Sub_Aggr));
4125 while Present (Assoc) loop
4126 Expr := Expression (Assoc);
4127 Check_Same_Aggr_Bounds (Expr, Dim + 1);
4128 Next (Assoc);
4129 end loop;
4130 end if;
4131 end if;
4132 end Check_Same_Aggr_Bounds;
4134 ----------------------------
4135 -- Compute_Others_Present --
4136 ----------------------------
4138 procedure Compute_Others_Present (Sub_Aggr : Node_Id; Dim : Pos) is
4139 Assoc : Node_Id;
4140 Expr : Node_Id;
4142 begin
4143 if Present (Component_Associations (Sub_Aggr)) then
4144 Assoc := Last (Component_Associations (Sub_Aggr));
4146 if Nkind (First (Choices (Assoc))) = N_Others_Choice then
4147 Others_Present (Dim) := True;
4148 end if;
4149 end if;
4151 -- Now look inside the sub-aggregate to see if there is more work
4153 if Dim < Aggr_Dimension then
4155 -- Process positional components
4157 if Present (Expressions (Sub_Aggr)) then
4158 Expr := First (Expressions (Sub_Aggr));
4159 while Present (Expr) loop
4160 Compute_Others_Present (Expr, Dim + 1);
4161 Next (Expr);
4162 end loop;
4163 end if;
4165 -- Process component associations
4167 if Present (Component_Associations (Sub_Aggr)) then
4168 Assoc := First (Component_Associations (Sub_Aggr));
4169 while Present (Assoc) loop
4170 Expr := Expression (Assoc);
4171 Compute_Others_Present (Expr, Dim + 1);
4172 Next (Assoc);
4173 end loop;
4174 end if;
4175 end if;
4176 end Compute_Others_Present;
4178 ------------------------
4179 -- In_Place_Assign_OK --
4180 ------------------------
4182 function In_Place_Assign_OK return Boolean is
4183 Aggr_In : Node_Id;
4184 Aggr_Lo : Node_Id;
4185 Aggr_Hi : Node_Id;
4186 Obj_In : Node_Id;
4187 Obj_Lo : Node_Id;
4188 Obj_Hi : Node_Id;
4190 function Safe_Aggregate (Aggr : Node_Id) return Boolean;
4191 -- Check recursively that each component of a (sub)aggregate does
4192 -- not depend on the variable being assigned to.
4194 function Safe_Component (Expr : Node_Id) return Boolean;
4195 -- Verify that an expression cannot depend on the variable being
4196 -- assigned to. Room for improvement here (but less than before).
4198 --------------------
4199 -- Safe_Aggregate --
4200 --------------------
4202 function Safe_Aggregate (Aggr : Node_Id) return Boolean is
4203 Expr : Node_Id;
4205 begin
4206 if Present (Expressions (Aggr)) then
4207 Expr := First (Expressions (Aggr));
4208 while Present (Expr) loop
4209 if Nkind (Expr) = N_Aggregate then
4210 if not Safe_Aggregate (Expr) then
4211 return False;
4212 end if;
4214 elsif not Safe_Component (Expr) then
4215 return False;
4216 end if;
4218 Next (Expr);
4219 end loop;
4220 end if;
4222 if Present (Component_Associations (Aggr)) then
4223 Expr := First (Component_Associations (Aggr));
4224 while Present (Expr) loop
4225 if Nkind (Expression (Expr)) = N_Aggregate then
4226 if not Safe_Aggregate (Expression (Expr)) then
4227 return False;
4228 end if;
4230 -- If association has a box, no way to determine yet
4231 -- whether default can be assigned in place.
4233 elsif Box_Present (Expr) then
4234 return False;
4236 elsif not Safe_Component (Expression (Expr)) then
4237 return False;
4238 end if;
4240 Next (Expr);
4241 end loop;
4242 end if;
4244 return True;
4245 end Safe_Aggregate;
4247 --------------------
4248 -- Safe_Component --
4249 --------------------
4251 function Safe_Component (Expr : Node_Id) return Boolean is
4252 Comp : Node_Id := Expr;
4254 function Check_Component (Comp : Node_Id) return Boolean;
4255 -- Do the recursive traversal, after copy
4257 ---------------------
4258 -- Check_Component --
4259 ---------------------
4261 function Check_Component (Comp : Node_Id) return Boolean is
4262 begin
4263 if Is_Overloaded (Comp) then
4264 return False;
4265 end if;
4267 return Compile_Time_Known_Value (Comp)
4269 or else (Is_Entity_Name (Comp)
4270 and then Present (Entity (Comp))
4271 and then No (Renamed_Object (Entity (Comp))))
4273 or else (Nkind (Comp) = N_Attribute_Reference
4274 and then Check_Component (Prefix (Comp)))
4276 or else (Nkind (Comp) in N_Binary_Op
4277 and then Check_Component (Left_Opnd (Comp))
4278 and then Check_Component (Right_Opnd (Comp)))
4280 or else (Nkind (Comp) in N_Unary_Op
4281 and then Check_Component (Right_Opnd (Comp)))
4283 or else (Nkind (Comp) = N_Selected_Component
4284 and then Check_Component (Prefix (Comp)))
4286 or else (Nkind (Comp) = N_Unchecked_Type_Conversion
4287 and then Check_Component (Expression (Comp)));
4288 end Check_Component;
4290 -- Start of processing for Safe_Component
4292 begin
4293 -- If the component appears in an association that may
4294 -- correspond to more than one element, it is not analyzed
4295 -- before the expansion into assignments, to avoid side effects.
4296 -- We analyze, but do not resolve the copy, to obtain sufficient
4297 -- entity information for the checks that follow. If component is
4298 -- overloaded we assume an unsafe function call.
4300 if not Analyzed (Comp) then
4301 if Is_Overloaded (Expr) then
4302 return False;
4304 elsif Nkind (Expr) = N_Aggregate
4305 and then not Is_Others_Aggregate (Expr)
4306 then
4307 return False;
4309 elsif Nkind (Expr) = N_Allocator then
4311 -- For now, too complex to analyze
4313 return False;
4314 end if;
4316 Comp := New_Copy_Tree (Expr);
4317 Set_Parent (Comp, Parent (Expr));
4318 Analyze (Comp);
4319 end if;
4321 if Nkind (Comp) = N_Aggregate then
4322 return Safe_Aggregate (Comp);
4323 else
4324 return Check_Component (Comp);
4325 end if;
4326 end Safe_Component;
4328 -- Start of processing for In_Place_Assign_OK
4330 begin
4331 if Present (Component_Associations (N)) then
4333 -- On assignment, sliding can take place, so we cannot do the
4334 -- assignment in place unless the bounds of the aggregate are
4335 -- statically equal to those of the target.
4337 -- If the aggregate is given by an others choice, the bounds
4338 -- are derived from the left-hand side, and the assignment is
4339 -- safe if the expression is.
4341 if Is_Others_Aggregate (N) then
4342 return
4343 Safe_Component
4344 (Expression (First (Component_Associations (N))));
4345 end if;
4347 Aggr_In := First_Index (Etype (N));
4349 if Nkind (Parent (N)) = N_Assignment_Statement then
4350 Obj_In := First_Index (Etype (Name (Parent (N))));
4352 else
4353 -- Context is an allocator. Check bounds of aggregate
4354 -- against given type in qualified expression.
4356 pragma Assert (Nkind (Parent (Parent (N))) = N_Allocator);
4357 Obj_In :=
4358 First_Index (Etype (Entity (Subtype_Mark (Parent (N)))));
4359 end if;
4361 while Present (Aggr_In) loop
4362 Get_Index_Bounds (Aggr_In, Aggr_Lo, Aggr_Hi);
4363 Get_Index_Bounds (Obj_In, Obj_Lo, Obj_Hi);
4365 if not Compile_Time_Known_Value (Aggr_Lo)
4366 or else not Compile_Time_Known_Value (Aggr_Hi)
4367 or else not Compile_Time_Known_Value (Obj_Lo)
4368 or else not Compile_Time_Known_Value (Obj_Hi)
4369 or else Expr_Value (Aggr_Lo) /= Expr_Value (Obj_Lo)
4370 or else Expr_Value (Aggr_Hi) /= Expr_Value (Obj_Hi)
4371 then
4372 return False;
4373 end if;
4375 Next_Index (Aggr_In);
4376 Next_Index (Obj_In);
4377 end loop;
4378 end if;
4380 -- Now check the component values themselves
4382 return Safe_Aggregate (N);
4383 end In_Place_Assign_OK;
4385 ------------------
4386 -- Others_Check --
4387 ------------------
4389 procedure Others_Check (Sub_Aggr : Node_Id; Dim : Pos) is
4390 Aggr_Lo : constant Node_Id := Aggr_Low (Dim);
4391 Aggr_Hi : constant Node_Id := Aggr_High (Dim);
4392 -- The bounds of the aggregate for this dimension
4394 Ind_Typ : constant Entity_Id := Aggr_Index_Typ (Dim);
4395 -- The index type for this dimension
4397 Need_To_Check : Boolean := False;
4399 Choices_Lo : Node_Id := Empty;
4400 Choices_Hi : Node_Id := Empty;
4401 -- The lowest and highest discrete choices for a named sub-aggregate
4403 Nb_Choices : Int := -1;
4404 -- The number of discrete non-others choices in this sub-aggregate
4406 Nb_Elements : Uint := Uint_0;
4407 -- The number of elements in a positional aggregate
4409 Cond : Node_Id := Empty;
4411 Assoc : Node_Id;
4412 Choice : Node_Id;
4413 Expr : Node_Id;
4415 begin
4416 -- Check if we have an others choice. If we do make sure that this
4417 -- sub-aggregate contains at least one element in addition to the
4418 -- others choice.
4420 if Range_Checks_Suppressed (Ind_Typ) then
4421 Need_To_Check := False;
4423 elsif Present (Expressions (Sub_Aggr))
4424 and then Present (Component_Associations (Sub_Aggr))
4425 then
4426 Need_To_Check := True;
4428 elsif Present (Component_Associations (Sub_Aggr)) then
4429 Assoc := Last (Component_Associations (Sub_Aggr));
4431 if Nkind (First (Choices (Assoc))) /= N_Others_Choice then
4432 Need_To_Check := False;
4434 else
4435 -- Count the number of discrete choices. Start with -1 because
4436 -- the others choice does not count.
4438 Nb_Choices := -1;
4439 Assoc := First (Component_Associations (Sub_Aggr));
4440 while Present (Assoc) loop
4441 Choice := First (Choices (Assoc));
4442 while Present (Choice) loop
4443 Nb_Choices := Nb_Choices + 1;
4444 Next (Choice);
4445 end loop;
4447 Next (Assoc);
4448 end loop;
4450 -- If there is only an others choice nothing to do
4452 Need_To_Check := (Nb_Choices > 0);
4453 end if;
4455 else
4456 Need_To_Check := False;
4457 end if;
4459 -- If we are dealing with a positional sub-aggregate with an others
4460 -- choice then compute the number or positional elements.
4462 if Need_To_Check and then Present (Expressions (Sub_Aggr)) then
4463 Expr := First (Expressions (Sub_Aggr));
4464 Nb_Elements := Uint_0;
4465 while Present (Expr) loop
4466 Nb_Elements := Nb_Elements + 1;
4467 Next (Expr);
4468 end loop;
4470 -- If the aggregate contains discrete choices and an others choice
4471 -- compute the smallest and largest discrete choice values.
4473 elsif Need_To_Check then
4474 Compute_Choices_Lo_And_Choices_Hi : declare
4476 Table : Case_Table_Type (1 .. Nb_Choices);
4477 -- Used to sort all the different choice values
4479 J : Pos := 1;
4480 Low : Node_Id;
4481 High : Node_Id;
4483 begin
4484 Assoc := First (Component_Associations (Sub_Aggr));
4485 while Present (Assoc) loop
4486 Choice := First (Choices (Assoc));
4487 while Present (Choice) loop
4488 if Nkind (Choice) = N_Others_Choice then
4489 exit;
4490 end if;
4492 Get_Index_Bounds (Choice, Low, High);
4493 Table (J).Choice_Lo := Low;
4494 Table (J).Choice_Hi := High;
4496 J := J + 1;
4497 Next (Choice);
4498 end loop;
4500 Next (Assoc);
4501 end loop;
4503 -- Sort the discrete choices
4505 Sort_Case_Table (Table);
4507 Choices_Lo := Table (1).Choice_Lo;
4508 Choices_Hi := Table (Nb_Choices).Choice_Hi;
4509 end Compute_Choices_Lo_And_Choices_Hi;
4510 end if;
4512 -- If no others choice in this sub-aggregate, or the aggregate
4513 -- comprises only an others choice, nothing to do.
4515 if not Need_To_Check then
4516 Cond := Empty;
4518 -- If we are dealing with an aggregate containing an others choice
4519 -- and positional components, we generate the following test:
4521 -- if Ind_Typ'Pos (Aggr_Lo) + (Nb_Elements - 1) >
4522 -- Ind_Typ'Pos (Aggr_Hi)
4523 -- then
4524 -- raise Constraint_Error;
4525 -- end if;
4527 elsif Nb_Elements > Uint_0 then
4528 Cond :=
4529 Make_Op_Gt (Loc,
4530 Left_Opnd =>
4531 Make_Op_Add (Loc,
4532 Left_Opnd =>
4533 Make_Attribute_Reference (Loc,
4534 Prefix => New_Reference_To (Ind_Typ, Loc),
4535 Attribute_Name => Name_Pos,
4536 Expressions =>
4537 New_List
4538 (Duplicate_Subexpr_Move_Checks (Aggr_Lo))),
4539 Right_Opnd => Make_Integer_Literal (Loc, Nb_Elements - 1)),
4541 Right_Opnd =>
4542 Make_Attribute_Reference (Loc,
4543 Prefix => New_Reference_To (Ind_Typ, Loc),
4544 Attribute_Name => Name_Pos,
4545 Expressions => New_List (
4546 Duplicate_Subexpr_Move_Checks (Aggr_Hi))));
4548 -- If we are dealing with an aggregate containing an others choice
4549 -- and discrete choices we generate the following test:
4551 -- [constraint_error when
4552 -- Choices_Lo < Aggr_Lo or else Choices_Hi > Aggr_Hi];
4554 else
4555 Cond :=
4556 Make_Or_Else (Loc,
4557 Left_Opnd =>
4558 Make_Op_Lt (Loc,
4559 Left_Opnd =>
4560 Duplicate_Subexpr_Move_Checks (Choices_Lo),
4561 Right_Opnd =>
4562 Duplicate_Subexpr_Move_Checks (Aggr_Lo)),
4564 Right_Opnd =>
4565 Make_Op_Gt (Loc,
4566 Left_Opnd =>
4567 Duplicate_Subexpr (Choices_Hi),
4568 Right_Opnd =>
4569 Duplicate_Subexpr (Aggr_Hi)));
4570 end if;
4572 if Present (Cond) then
4573 Insert_Action (N,
4574 Make_Raise_Constraint_Error (Loc,
4575 Condition => Cond,
4576 Reason => CE_Length_Check_Failed));
4577 -- Questionable reason code, shouldn't that be a
4578 -- CE_Range_Check_Failed ???
4579 end if;
4581 -- Now look inside the sub-aggregate to see if there is more work
4583 if Dim < Aggr_Dimension then
4585 -- Process positional components
4587 if Present (Expressions (Sub_Aggr)) then
4588 Expr := First (Expressions (Sub_Aggr));
4589 while Present (Expr) loop
4590 Others_Check (Expr, Dim + 1);
4591 Next (Expr);
4592 end loop;
4593 end if;
4595 -- Process component associations
4597 if Present (Component_Associations (Sub_Aggr)) then
4598 Assoc := First (Component_Associations (Sub_Aggr));
4599 while Present (Assoc) loop
4600 Expr := Expression (Assoc);
4601 Others_Check (Expr, Dim + 1);
4602 Next (Assoc);
4603 end loop;
4604 end if;
4605 end if;
4606 end Others_Check;
4608 -------------------------
4609 -- Safe_Left_Hand_Side --
4610 -------------------------
4612 function Safe_Left_Hand_Side (N : Node_Id) return Boolean is
4613 function Is_Safe_Index (Indx : Node_Id) return Boolean;
4614 -- If the left-hand side includes an indexed component, check that
4615 -- the indexes are free of side-effect.
4617 -------------------
4618 -- Is_Safe_Index --
4619 -------------------
4621 function Is_Safe_Index (Indx : Node_Id) return Boolean is
4622 begin
4623 if Is_Entity_Name (Indx) then
4624 return True;
4626 elsif Nkind (Indx) = N_Integer_Literal then
4627 return True;
4629 elsif Nkind (Indx) = N_Function_Call
4630 and then Is_Entity_Name (Name (Indx))
4631 and then
4632 Has_Pragma_Pure_Function (Entity (Name (Indx)))
4633 then
4634 return True;
4636 elsif Nkind (Indx) = N_Type_Conversion
4637 and then Is_Safe_Index (Expression (Indx))
4638 then
4639 return True;
4641 else
4642 return False;
4643 end if;
4644 end Is_Safe_Index;
4646 -- Start of processing for Safe_Left_Hand_Side
4648 begin
4649 if Is_Entity_Name (N) then
4650 return True;
4652 elsif Nkind_In (N, N_Explicit_Dereference, N_Selected_Component)
4653 and then Safe_Left_Hand_Side (Prefix (N))
4654 then
4655 return True;
4657 elsif Nkind (N) = N_Indexed_Component
4658 and then Safe_Left_Hand_Side (Prefix (N))
4659 and then
4660 Is_Safe_Index (First (Expressions (N)))
4661 then
4662 return True;
4664 elsif Nkind (N) = N_Unchecked_Type_Conversion then
4665 return Safe_Left_Hand_Side (Expression (N));
4667 else
4668 return False;
4669 end if;
4670 end Safe_Left_Hand_Side;
4672 -- Local variables
4674 Tmp : Entity_Id;
4675 -- Holds the temporary aggregate value
4677 Tmp_Decl : Node_Id;
4678 -- Holds the declaration of Tmp
4680 Aggr_Code : List_Id;
4681 Parent_Node : Node_Id;
4682 Parent_Kind : Node_Kind;
4684 -- Start of processing for Expand_Array_Aggregate
4686 begin
4687 -- Do not touch the special aggregates of attributes used for Asm calls
4689 if Is_RTE (Ctyp, RE_Asm_Input_Operand)
4690 or else Is_RTE (Ctyp, RE_Asm_Output_Operand)
4691 then
4692 return;
4694 -- Do not expand an aggregate for an array type which contains tasks if
4695 -- the aggregate is associated with an unexpanded return statement of a
4696 -- build-in-place function. The aggregate is expanded when the related
4697 -- return statement (rewritten into an extended return) is processed.
4698 -- This delay ensures that any temporaries and initialization code
4699 -- generated for the aggregate appear in the proper return block and
4700 -- use the correct _chain and _master.
4702 elsif Has_Task (Base_Type (Etype (N)))
4703 and then Nkind (Parent (N)) = N_Simple_Return_Statement
4704 and then Is_Build_In_Place_Function
4705 (Return_Applies_To (Return_Statement_Entity (Parent (N))))
4706 then
4707 return;
4708 end if;
4710 -- If the semantic analyzer has determined that aggregate N will raise
4711 -- Constraint_Error at run time, then the aggregate node has been
4712 -- replaced with an N_Raise_Constraint_Error node and we should
4713 -- never get here.
4715 pragma Assert (not Raises_Constraint_Error (N));
4717 -- STEP 1a
4719 -- Check that the index range defined by aggregate bounds is
4720 -- compatible with corresponding index subtype.
4722 Index_Compatibility_Check : declare
4723 Aggr_Index_Range : Node_Id := First_Index (Typ);
4724 -- The current aggregate index range
4726 Index_Constraint : Node_Id := First_Index (Etype (Typ));
4727 -- The corresponding index constraint against which we have to
4728 -- check the above aggregate index range.
4730 begin
4731 Compute_Others_Present (N, 1);
4733 for J in 1 .. Aggr_Dimension loop
4734 -- There is no need to emit a check if an others choice is
4735 -- present for this array aggregate dimension since in this
4736 -- case one of N's sub-aggregates has taken its bounds from the
4737 -- context and these bounds must have been checked already. In
4738 -- addition all sub-aggregates corresponding to the same
4739 -- dimension must all have the same bounds (checked in (c) below).
4741 if not Range_Checks_Suppressed (Etype (Index_Constraint))
4742 and then not Others_Present (J)
4743 then
4744 -- We don't use Checks.Apply_Range_Check here because it emits
4745 -- a spurious check. Namely it checks that the range defined by
4746 -- the aggregate bounds is non empty. But we know this already
4747 -- if we get here.
4749 Check_Bounds (Aggr_Index_Range, Index_Constraint);
4750 end if;
4752 -- Save the low and high bounds of the aggregate index as well as
4753 -- the index type for later use in checks (b) and (c) below.
4755 Aggr_Low (J) := Low_Bound (Aggr_Index_Range);
4756 Aggr_High (J) := High_Bound (Aggr_Index_Range);
4758 Aggr_Index_Typ (J) := Etype (Index_Constraint);
4760 Next_Index (Aggr_Index_Range);
4761 Next_Index (Index_Constraint);
4762 end loop;
4763 end Index_Compatibility_Check;
4765 -- STEP 1b
4767 -- If an others choice is present check that no aggregate index is
4768 -- outside the bounds of the index constraint.
4770 Others_Check (N, 1);
4772 -- STEP 1c
4774 -- For multidimensional arrays make sure that all subaggregates
4775 -- corresponding to the same dimension have the same bounds.
4777 if Aggr_Dimension > 1 then
4778 Check_Same_Aggr_Bounds (N, 1);
4779 end if;
4781 -- STEP 2
4783 -- Here we test for is packed array aggregate that we can handle at
4784 -- compile time. If so, return with transformation done. Note that we do
4785 -- this even if the aggregate is nested, because once we have done this
4786 -- processing, there is no more nested aggregate!
4788 if Packed_Array_Aggregate_Handled (N) then
4789 return;
4790 end if;
4792 -- At this point we try to convert to positional form
4794 if Ekind (Current_Scope) = E_Package
4795 and then Static_Elaboration_Desired (Current_Scope)
4796 then
4797 Convert_To_Positional (N, Max_Others_Replicate => 100);
4798 else
4799 Convert_To_Positional (N);
4800 end if;
4802 -- if the result is no longer an aggregate (e.g. it may be a string
4803 -- literal, or a temporary which has the needed value), then we are
4804 -- done, since there is no longer a nested aggregate.
4806 if Nkind (N) /= N_Aggregate then
4807 return;
4809 -- We are also done if the result is an analyzed aggregate, indicating
4810 -- that Convert_To_Positional succeeded and reanalyzed the rewritten
4811 -- aggregate.
4813 elsif Analyzed (N)
4814 and then N /= Original_Node (N)
4815 then
4816 return;
4817 end if;
4819 -- If all aggregate components are compile-time known and the aggregate
4820 -- has been flattened, nothing left to do. The same occurs if the
4821 -- aggregate is used to initialize the components of an statically
4822 -- allocated dispatch table.
4824 if Compile_Time_Known_Aggregate (N)
4825 or else Is_Static_Dispatch_Table_Aggregate (N)
4826 then
4827 Set_Expansion_Delayed (N, False);
4828 return;
4829 end if;
4831 -- Now see if back end processing is possible
4833 if Backend_Processing_Possible (N) then
4835 -- If the aggregate is static but the constraints are not, build
4836 -- a static subtype for the aggregate, so that Gigi can place it
4837 -- in static memory. Perform an unchecked_conversion to the non-
4838 -- static type imposed by the context.
4840 declare
4841 Itype : constant Entity_Id := Etype (N);
4842 Index : Node_Id;
4843 Needs_Type : Boolean := False;
4845 begin
4846 Index := First_Index (Itype);
4847 while Present (Index) loop
4848 if not Is_Static_Subtype (Etype (Index)) then
4849 Needs_Type := True;
4850 exit;
4851 else
4852 Next_Index (Index);
4853 end if;
4854 end loop;
4856 if Needs_Type then
4857 Build_Constrained_Type (Positional => True);
4858 Rewrite (N, Unchecked_Convert_To (Itype, N));
4859 Analyze (N);
4860 end if;
4861 end;
4863 return;
4864 end if;
4866 -- STEP 3
4868 -- Delay expansion for nested aggregates: it will be taken care of
4869 -- when the parent aggregate is expanded.
4871 Parent_Node := Parent (N);
4872 Parent_Kind := Nkind (Parent_Node);
4874 if Parent_Kind = N_Qualified_Expression then
4875 Parent_Node := Parent (Parent_Node);
4876 Parent_Kind := Nkind (Parent_Node);
4877 end if;
4879 if Parent_Kind = N_Aggregate
4880 or else Parent_Kind = N_Extension_Aggregate
4881 or else Parent_Kind = N_Component_Association
4882 or else (Parent_Kind = N_Object_Declaration
4883 and then Needs_Finalization (Typ))
4884 or else (Parent_Kind = N_Assignment_Statement
4885 and then Inside_Init_Proc)
4886 then
4887 if Static_Array_Aggregate (N)
4888 or else Compile_Time_Known_Aggregate (N)
4889 then
4890 Set_Expansion_Delayed (N, False);
4891 return;
4892 else
4893 Set_Expansion_Delayed (N);
4894 return;
4895 end if;
4896 end if;
4898 -- STEP 4
4900 -- Look if in place aggregate expansion is possible
4902 -- For object declarations we build the aggregate in place, unless
4903 -- the array is bit-packed or the component is controlled.
4905 -- For assignments we do the assignment in place if all the component
4906 -- associations have compile-time known values. For other cases we
4907 -- create a temporary. The analysis for safety of on-line assignment
4908 -- is delicate, i.e. we don't know how to do it fully yet ???
4910 -- For allocators we assign to the designated object in place if the
4911 -- aggregate meets the same conditions as other in-place assignments.
4912 -- In this case the aggregate may not come from source but was created
4913 -- for default initialization, e.g. with Initialize_Scalars.
4915 if Requires_Transient_Scope (Typ) then
4916 Establish_Transient_Scope
4917 (N, Sec_Stack => Has_Controlled_Component (Typ));
4918 end if;
4920 if Has_Default_Init_Comps (N) then
4921 Maybe_In_Place_OK := False;
4923 elsif Is_Bit_Packed_Array (Typ)
4924 or else Has_Controlled_Component (Typ)
4925 then
4926 Maybe_In_Place_OK := False;
4928 else
4929 Maybe_In_Place_OK :=
4930 (Nkind (Parent (N)) = N_Assignment_Statement
4931 and then Comes_From_Source (N)
4932 and then In_Place_Assign_OK)
4934 or else
4935 (Nkind (Parent (Parent (N))) = N_Allocator
4936 and then In_Place_Assign_OK);
4937 end if;
4939 -- If this is an array of tasks, it will be expanded into build-in-place
4940 -- assignments. Build an activation chain for the tasks now.
4942 if Has_Task (Etype (N)) then
4943 Build_Activation_Chain_Entity (N);
4944 end if;
4946 -- Should document these individual tests ???
4948 if not Has_Default_Init_Comps (N)
4949 and then Comes_From_Source (Parent (N))
4950 and then Nkind (Parent (N)) = N_Object_Declaration
4951 and then not
4952 Must_Slide (Etype (Defining_Identifier (Parent (N))), Typ)
4953 and then N = Expression (Parent (N))
4954 and then not Is_Bit_Packed_Array (Typ)
4955 and then not Has_Controlled_Component (Typ)
4957 -- If the aggregate is the expression in an object declaration, it
4958 -- cannot be expanded in place. Lookahead in the current declarative
4959 -- part to find an address clause for the object being declared. If
4960 -- one is present, we cannot build in place. Unclear comment???
4962 and then not Has_Following_Address_Clause (Parent (N))
4963 then
4964 Tmp := Defining_Identifier (Parent (N));
4965 Set_No_Initialization (Parent (N));
4966 Set_Expression (Parent (N), Empty);
4968 -- Set the type of the entity, for use in the analysis of the
4969 -- subsequent indexed assignments. If the nominal type is not
4970 -- constrained, build a subtype from the known bounds of the
4971 -- aggregate. If the declaration has a subtype mark, use it,
4972 -- otherwise use the itype of the aggregate.
4974 if not Is_Constrained (Typ) then
4975 Build_Constrained_Type (Positional => False);
4976 elsif Is_Entity_Name (Object_Definition (Parent (N)))
4977 and then Is_Constrained (Entity (Object_Definition (Parent (N))))
4978 then
4979 Set_Etype (Tmp, Entity (Object_Definition (Parent (N))));
4980 else
4981 Set_Size_Known_At_Compile_Time (Typ, False);
4982 Set_Etype (Tmp, Typ);
4983 end if;
4985 elsif Maybe_In_Place_OK
4986 and then Nkind (Parent (N)) = N_Qualified_Expression
4987 and then Nkind (Parent (Parent (N))) = N_Allocator
4988 then
4989 Set_Expansion_Delayed (N);
4990 return;
4992 -- In the remaining cases the aggregate is the RHS of an assignment
4994 elsif Maybe_In_Place_OK
4995 and then Safe_Left_Hand_Side (Name (Parent (N)))
4996 then
4997 Tmp := Name (Parent (N));
4999 if Etype (Tmp) /= Etype (N) then
5000 Apply_Length_Check (N, Etype (Tmp));
5002 if Nkind (N) = N_Raise_Constraint_Error then
5004 -- Static error, nothing further to expand
5006 return;
5007 end if;
5008 end if;
5010 elsif Maybe_In_Place_OK
5011 and then Nkind (Name (Parent (N))) = N_Slice
5012 and then Safe_Slice_Assignment (N)
5013 then
5014 -- Safe_Slice_Assignment rewrites assignment as a loop
5016 return;
5018 -- Step 5
5020 -- In place aggregate expansion is not possible
5022 else
5023 Maybe_In_Place_OK := False;
5024 Tmp := Make_Temporary (Loc, 'A', N);
5025 Tmp_Decl :=
5026 Make_Object_Declaration
5027 (Loc,
5028 Defining_Identifier => Tmp,
5029 Object_Definition => New_Occurrence_Of (Typ, Loc));
5030 Set_No_Initialization (Tmp_Decl, True);
5032 -- If we are within a loop, the temporary will be pushed on the
5033 -- stack at each iteration. If the aggregate is the expression for an
5034 -- allocator, it will be immediately copied to the heap and can
5035 -- be reclaimed at once. We create a transient scope around the
5036 -- aggregate for this purpose.
5038 if Ekind (Current_Scope) = E_Loop
5039 and then Nkind (Parent (Parent (N))) = N_Allocator
5040 then
5041 Establish_Transient_Scope (N, False);
5042 end if;
5044 Insert_Action (N, Tmp_Decl);
5045 end if;
5047 -- Construct and insert the aggregate code. We can safely suppress index
5048 -- checks because this code is guaranteed not to raise CE on index
5049 -- checks. However we should *not* suppress all checks.
5051 declare
5052 Target : Node_Id;
5054 begin
5055 if Nkind (Tmp) = N_Defining_Identifier then
5056 Target := New_Reference_To (Tmp, Loc);
5058 else
5060 if Has_Default_Init_Comps (N) then
5062 -- Ada 2005 (AI-287): This case has not been analyzed???
5064 raise Program_Error;
5065 end if;
5067 -- Name in assignment is explicit dereference
5069 Target := New_Copy (Tmp);
5070 end if;
5072 Aggr_Code :=
5073 Build_Array_Aggr_Code (N,
5074 Ctype => Ctyp,
5075 Index => First_Index (Typ),
5076 Into => Target,
5077 Scalar_Comp => Is_Scalar_Type (Ctyp));
5078 end;
5080 if Comes_From_Source (Tmp) then
5081 Insert_Actions_After (Parent (N), Aggr_Code);
5083 else
5084 Insert_Actions (N, Aggr_Code);
5085 end if;
5087 -- If the aggregate has been assigned in place, remove the original
5088 -- assignment.
5090 if Nkind (Parent (N)) = N_Assignment_Statement
5091 and then Maybe_In_Place_OK
5092 then
5093 Rewrite (Parent (N), Make_Null_Statement (Loc));
5095 elsif Nkind (Parent (N)) /= N_Object_Declaration
5096 or else Tmp /= Defining_Identifier (Parent (N))
5097 then
5098 Rewrite (N, New_Occurrence_Of (Tmp, Loc));
5099 Analyze_And_Resolve (N, Typ);
5100 end if;
5101 end Expand_Array_Aggregate;
5103 ------------------------
5104 -- Expand_N_Aggregate --
5105 ------------------------
5107 procedure Expand_N_Aggregate (N : Node_Id) is
5108 begin
5109 if Is_Record_Type (Etype (N)) then
5110 Expand_Record_Aggregate (N);
5111 else
5112 Expand_Array_Aggregate (N);
5113 end if;
5114 exception
5115 when RE_Not_Available =>
5116 return;
5117 end Expand_N_Aggregate;
5119 ----------------------------------
5120 -- Expand_N_Extension_Aggregate --
5121 ----------------------------------
5123 -- If the ancestor part is an expression, add a component association for
5124 -- the parent field. If the type of the ancestor part is not the direct
5125 -- parent of the expected type, build recursively the needed ancestors.
5126 -- If the ancestor part is a subtype_mark, replace aggregate with a decla-
5127 -- ration for a temporary of the expected type, followed by individual
5128 -- assignments to the given components.
5130 procedure Expand_N_Extension_Aggregate (N : Node_Id) is
5131 Loc : constant Source_Ptr := Sloc (N);
5132 A : constant Node_Id := Ancestor_Part (N);
5133 Typ : constant Entity_Id := Etype (N);
5135 begin
5136 -- If the ancestor is a subtype mark, an init proc must be called
5137 -- on the resulting object which thus has to be materialized in
5138 -- the front-end
5140 if Is_Entity_Name (A) and then Is_Type (Entity (A)) then
5141 Convert_To_Assignments (N, Typ);
5143 -- The extension aggregate is transformed into a record aggregate
5144 -- of the following form (c1 and c2 are inherited components)
5146 -- (Exp with c3 => a, c4 => b)
5147 -- ==> (c1 => Exp.c1, c2 => Exp.c2, c3 => a, c4 => b)
5149 else
5150 Set_Etype (N, Typ);
5152 if Tagged_Type_Expansion then
5153 Expand_Record_Aggregate (N,
5154 Orig_Tag =>
5155 New_Occurrence_Of
5156 (Node (First_Elmt (Access_Disp_Table (Typ))), Loc),
5157 Parent_Expr => A);
5159 -- No tag is needed in the case of a VM
5161 else
5162 Expand_Record_Aggregate (N, Parent_Expr => A);
5163 end if;
5164 end if;
5166 exception
5167 when RE_Not_Available =>
5168 return;
5169 end Expand_N_Extension_Aggregate;
5171 -----------------------------
5172 -- Expand_Record_Aggregate --
5173 -----------------------------
5175 procedure Expand_Record_Aggregate
5176 (N : Node_Id;
5177 Orig_Tag : Node_Id := Empty;
5178 Parent_Expr : Node_Id := Empty)
5180 Loc : constant Source_Ptr := Sloc (N);
5181 Comps : constant List_Id := Component_Associations (N);
5182 Typ : constant Entity_Id := Etype (N);
5183 Base_Typ : constant Entity_Id := Base_Type (Typ);
5185 Static_Components : Boolean := True;
5186 -- Flag to indicate whether all components are compile-time known,
5187 -- and the aggregate can be constructed statically and handled by
5188 -- the back-end.
5190 function Compile_Time_Known_Composite_Value (N : Node_Id) return Boolean;
5191 -- Returns true if N is an expression of composite type which can be
5192 -- fully evaluated at compile time without raising constraint error.
5193 -- Such expressions can be passed as is to Gigi without any expansion.
5195 -- This returns true for N_Aggregate with Compile_Time_Known_Aggregate
5196 -- set and constants whose expression is such an aggregate, recursively.
5198 function Component_Not_OK_For_Backend return Boolean;
5199 -- Check for presence of component which makes it impossible for the
5200 -- backend to process the aggregate, thus requiring the use of a series
5201 -- of assignment statements. Cases checked for are a nested aggregate
5202 -- needing Late_Expansion, the presence of a tagged component which may
5203 -- need tag adjustment, and a bit unaligned component reference.
5205 -- We also force expansion into assignments if a component is of a
5206 -- mutable type (including a private type with discriminants) because
5207 -- in that case the size of the component to be copied may be smaller
5208 -- than the side of the target, and there is no simple way for gigi
5209 -- to compute the size of the object to be copied.
5211 -- NOTE: This is part of the ongoing work to define precisely the
5212 -- interface between front-end and back-end handling of aggregates.
5213 -- In general it is desirable to pass aggregates as they are to gigi,
5214 -- in order to minimize elaboration code. This is one case where the
5215 -- semantics of Ada complicate the analysis and lead to anomalies in
5216 -- the gcc back-end if the aggregate is not expanded into assignments.
5218 function Has_Visible_Private_Ancestor (Id : E) return Boolean;
5219 -- If any ancestor of the current type is private, the aggregate
5220 -- cannot be built in place. We canot rely on Has_Private_Ancestor,
5221 -- because it will not be set when type and its parent are in the
5222 -- same scope, and the parent component needs expansion.
5224 function Top_Level_Aggregate (N : Node_Id) return Node_Id;
5225 -- For nested aggregates return the ultimate enclosing aggregate; for
5226 -- non-nested aggregates return N.
5228 ----------------------------------------
5229 -- Compile_Time_Known_Composite_Value --
5230 ----------------------------------------
5232 function Compile_Time_Known_Composite_Value
5233 (N : Node_Id) return Boolean
5235 begin
5236 -- If we have an entity name, then see if it is the name of a
5237 -- constant and if so, test the corresponding constant value.
5239 if Is_Entity_Name (N) then
5240 declare
5241 E : constant Entity_Id := Entity (N);
5242 V : Node_Id;
5243 begin
5244 if Ekind (E) /= E_Constant then
5245 return False;
5246 else
5247 V := Constant_Value (E);
5248 return Present (V)
5249 and then Compile_Time_Known_Composite_Value (V);
5250 end if;
5251 end;
5253 -- We have a value, see if it is compile time known
5255 else
5256 if Nkind (N) = N_Aggregate then
5257 return Compile_Time_Known_Aggregate (N);
5258 end if;
5260 -- All other types of values are not known at compile time
5262 return False;
5263 end if;
5265 end Compile_Time_Known_Composite_Value;
5267 ----------------------------------
5268 -- Component_Not_OK_For_Backend --
5269 ----------------------------------
5271 function Component_Not_OK_For_Backend return Boolean is
5272 C : Node_Id;
5273 Expr_Q : Node_Id;
5275 begin
5276 if No (Comps) then
5277 return False;
5278 end if;
5280 C := First (Comps);
5281 while Present (C) loop
5283 -- If the component has box initialization, expansion is needed
5284 -- and component is not ready for backend.
5286 if Box_Present (C) then
5287 return True;
5288 end if;
5290 if Nkind (Expression (C)) = N_Qualified_Expression then
5291 Expr_Q := Expression (Expression (C));
5292 else
5293 Expr_Q := Expression (C);
5294 end if;
5296 -- Return true if the aggregate has any associations for tagged
5297 -- components that may require tag adjustment.
5299 -- These are cases where the source expression may have a tag that
5300 -- could differ from the component tag (e.g., can occur for type
5301 -- conversions and formal parameters). (Tag adjustment not needed
5302 -- if VM_Target because object tags are implicit in the machine.)
5304 if Is_Tagged_Type (Etype (Expr_Q))
5305 and then (Nkind (Expr_Q) = N_Type_Conversion
5306 or else (Is_Entity_Name (Expr_Q)
5307 and then
5308 Ekind (Entity (Expr_Q)) in Formal_Kind))
5309 and then Tagged_Type_Expansion
5310 then
5311 Static_Components := False;
5312 return True;
5314 elsif Is_Delayed_Aggregate (Expr_Q) then
5315 Static_Components := False;
5316 return True;
5318 elsif Possible_Bit_Aligned_Component (Expr_Q) then
5319 Static_Components := False;
5320 return True;
5321 end if;
5323 if Is_Elementary_Type (Etype (Expr_Q)) then
5324 if not Compile_Time_Known_Value (Expr_Q) then
5325 Static_Components := False;
5326 end if;
5328 elsif not Compile_Time_Known_Composite_Value (Expr_Q) then
5329 Static_Components := False;
5331 if Is_Private_Type (Etype (Expr_Q))
5332 and then Has_Discriminants (Etype (Expr_Q))
5333 then
5334 return True;
5335 end if;
5336 end if;
5338 Next (C);
5339 end loop;
5341 return False;
5342 end Component_Not_OK_For_Backend;
5344 -----------------------------------
5345 -- Has_Visible_Private_Ancestor --
5346 -----------------------------------
5348 function Has_Visible_Private_Ancestor (Id : E) return Boolean is
5349 R : constant Entity_Id := Root_Type (Id);
5350 T1 : Entity_Id := Id;
5352 begin
5353 loop
5354 if Is_Private_Type (T1) then
5355 return True;
5357 elsif T1 = R then
5358 return False;
5360 else
5361 T1 := Etype (T1);
5362 end if;
5363 end loop;
5364 end Has_Visible_Private_Ancestor;
5366 -------------------------
5367 -- Top_Level_Aggregate --
5368 -------------------------
5370 function Top_Level_Aggregate (N : Node_Id) return Node_Id is
5371 Aggr : Node_Id;
5373 begin
5374 Aggr := N;
5375 while Present (Parent (Aggr))
5376 and then Nkind_In (Parent (Aggr), N_Component_Association,
5377 N_Aggregate)
5378 loop
5379 Aggr := Parent (Aggr);
5380 end loop;
5382 return Aggr;
5383 end Top_Level_Aggregate;
5385 -- Local variables
5387 Top_Level_Aggr : constant Node_Id := Top_Level_Aggregate (N);
5388 Tag_Value : Node_Id;
5389 Comp : Entity_Id;
5390 New_Comp : Node_Id;
5392 -- Start of processing for Expand_Record_Aggregate
5394 begin
5395 -- If the aggregate is to be assigned to an atomic variable, we
5396 -- have to prevent a piecemeal assignment even if the aggregate
5397 -- is to be expanded. We create a temporary for the aggregate, and
5398 -- assign the temporary instead, so that the back end can generate
5399 -- an atomic move for it.
5401 if Is_Atomic (Typ)
5402 and then Comes_From_Source (Parent (N))
5403 and then Is_Atomic_Aggregate (N, Typ)
5404 then
5405 return;
5407 -- No special management required for aggregates used to initialize
5408 -- statically allocated dispatch tables
5410 elsif Is_Static_Dispatch_Table_Aggregate (N) then
5411 return;
5412 end if;
5414 -- Ada 2005 (AI-318-2): We need to convert to assignments if components
5415 -- are build-in-place function calls. The assignments will each turn
5416 -- into a build-in-place function call. If components are all static,
5417 -- we can pass the aggregate to the backend regardless of limitedness.
5419 -- Extension aggregates, aggregates in extended return statements, and
5420 -- aggregates for C++ imported types must be expanded.
5422 if Ada_Version >= Ada_2005 and then Is_Immutably_Limited_Type (Typ) then
5423 if not Nkind_In (Parent (N), N_Object_Declaration,
5424 N_Component_Association)
5425 then
5426 Convert_To_Assignments (N, Typ);
5428 elsif Nkind (N) = N_Extension_Aggregate
5429 or else Convention (Typ) = Convention_CPP
5430 then
5431 Convert_To_Assignments (N, Typ);
5433 elsif not Size_Known_At_Compile_Time (Typ)
5434 or else Component_Not_OK_For_Backend
5435 or else not Static_Components
5436 then
5437 Convert_To_Assignments (N, Typ);
5439 else
5440 Set_Compile_Time_Known_Aggregate (N);
5441 Set_Expansion_Delayed (N, False);
5442 end if;
5444 -- Gigi doesn't properly handle temporaries of variable size so we
5445 -- generate it in the front-end
5447 elsif not Size_Known_At_Compile_Time (Typ)
5448 and then Tagged_Type_Expansion
5449 then
5450 Convert_To_Assignments (N, Typ);
5452 -- Temporaries for controlled aggregates need to be attached to a final
5453 -- chain in order to be properly finalized, so it has to be created in
5454 -- the front-end
5456 elsif Is_Controlled (Typ)
5457 or else Has_Controlled_Component (Base_Type (Typ))
5458 then
5459 Convert_To_Assignments (N, Typ);
5461 -- Ada 2005 (AI-287): In case of default initialized components we
5462 -- convert the aggregate into assignments.
5464 elsif Has_Default_Init_Comps (N) then
5465 Convert_To_Assignments (N, Typ);
5467 -- Check components
5469 elsif Component_Not_OK_For_Backend then
5470 Convert_To_Assignments (N, Typ);
5472 -- If an ancestor is private, some components are not inherited and we
5473 -- cannot expand into a record aggregate.
5475 elsif Has_Visible_Private_Ancestor (Typ) then
5476 Convert_To_Assignments (N, Typ);
5478 -- ??? The following was done to compile fxacc00.ads in the ACVCs. Gigi
5479 -- is not able to handle the aggregate for Late_Request.
5481 elsif Is_Tagged_Type (Typ) and then Has_Discriminants (Typ) then
5482 Convert_To_Assignments (N, Typ);
5484 -- If the tagged types covers interface types we need to initialize all
5485 -- hidden components containing pointers to secondary dispatch tables.
5487 elsif Is_Tagged_Type (Typ) and then Has_Interfaces (Typ) then
5488 Convert_To_Assignments (N, Typ);
5490 -- If some components are mutable, the size of the aggregate component
5491 -- may be distinct from the default size of the type component, so
5492 -- we need to expand to insure that the back-end copies the proper
5493 -- size of the data. However, if the aggregate is the initial value of
5494 -- a constant, the target is immutable and might be built statically
5495 -- if components are appropriate.
5497 elsif Has_Mutable_Components (Typ)
5498 and then
5499 (Nkind (Parent (Top_Level_Aggr)) /= N_Object_Declaration
5500 or else not Constant_Present (Parent (Top_Level_Aggr))
5501 or else not Static_Components)
5502 then
5503 Convert_To_Assignments (N, Typ);
5505 -- If the type involved has any non-bit aligned components, then we are
5506 -- not sure that the back end can handle this case correctly.
5508 elsif Type_May_Have_Bit_Aligned_Components (Typ) then
5509 Convert_To_Assignments (N, Typ);
5511 -- In all other cases, build a proper aggregate handlable by gigi
5513 else
5514 if Nkind (N) = N_Aggregate then
5516 -- If the aggregate is static and can be handled by the back-end,
5517 -- nothing left to do.
5519 if Static_Components then
5520 Set_Compile_Time_Known_Aggregate (N);
5521 Set_Expansion_Delayed (N, False);
5522 end if;
5523 end if;
5525 -- If no discriminants, nothing special to do
5527 if not Has_Discriminants (Typ) then
5528 null;
5530 -- Case of discriminants present
5532 elsif Is_Derived_Type (Typ) then
5534 -- For untagged types, non-stored discriminants are replaced
5535 -- with stored discriminants, which are the ones that gigi uses
5536 -- to describe the type and its components.
5538 Generate_Aggregate_For_Derived_Type : declare
5539 Constraints : constant List_Id := New_List;
5540 First_Comp : Node_Id;
5541 Discriminant : Entity_Id;
5542 Decl : Node_Id;
5543 Num_Disc : Int := 0;
5544 Num_Gird : Int := 0;
5546 procedure Prepend_Stored_Values (T : Entity_Id);
5547 -- Scan the list of stored discriminants of the type, and add
5548 -- their values to the aggregate being built.
5550 ---------------------------
5551 -- Prepend_Stored_Values --
5552 ---------------------------
5554 procedure Prepend_Stored_Values (T : Entity_Id) is
5555 begin
5556 Discriminant := First_Stored_Discriminant (T);
5557 while Present (Discriminant) loop
5558 New_Comp :=
5559 Make_Component_Association (Loc,
5560 Choices =>
5561 New_List (New_Occurrence_Of (Discriminant, Loc)),
5563 Expression =>
5564 New_Copy_Tree (
5565 Get_Discriminant_Value (
5566 Discriminant,
5567 Typ,
5568 Discriminant_Constraint (Typ))));
5570 if No (First_Comp) then
5571 Prepend_To (Component_Associations (N), New_Comp);
5572 else
5573 Insert_After (First_Comp, New_Comp);
5574 end if;
5576 First_Comp := New_Comp;
5577 Next_Stored_Discriminant (Discriminant);
5578 end loop;
5579 end Prepend_Stored_Values;
5581 -- Start of processing for Generate_Aggregate_For_Derived_Type
5583 begin
5584 -- Remove the associations for the discriminant of derived type
5586 First_Comp := First (Component_Associations (N));
5587 while Present (First_Comp) loop
5588 Comp := First_Comp;
5589 Next (First_Comp);
5591 if Ekind (Entity
5592 (First (Choices (Comp)))) = E_Discriminant
5593 then
5594 Remove (Comp);
5595 Num_Disc := Num_Disc + 1;
5596 end if;
5597 end loop;
5599 -- Insert stored discriminant associations in the correct
5600 -- order. If there are more stored discriminants than new
5601 -- discriminants, there is at least one new discriminant that
5602 -- constrains more than one of the stored discriminants. In
5603 -- this case we need to construct a proper subtype of the
5604 -- parent type, in order to supply values to all the
5605 -- components. Otherwise there is one-one correspondence
5606 -- between the constraints and the stored discriminants.
5608 First_Comp := Empty;
5610 Discriminant := First_Stored_Discriminant (Base_Type (Typ));
5611 while Present (Discriminant) loop
5612 Num_Gird := Num_Gird + 1;
5613 Next_Stored_Discriminant (Discriminant);
5614 end loop;
5616 -- Case of more stored discriminants than new discriminants
5618 if Num_Gird > Num_Disc then
5620 -- Create a proper subtype of the parent type, which is the
5621 -- proper implementation type for the aggregate, and convert
5622 -- it to the intended target type.
5624 Discriminant := First_Stored_Discriminant (Base_Type (Typ));
5625 while Present (Discriminant) loop
5626 New_Comp :=
5627 New_Copy_Tree (
5628 Get_Discriminant_Value (
5629 Discriminant,
5630 Typ,
5631 Discriminant_Constraint (Typ)));
5632 Append (New_Comp, Constraints);
5633 Next_Stored_Discriminant (Discriminant);
5634 end loop;
5636 Decl :=
5637 Make_Subtype_Declaration (Loc,
5638 Defining_Identifier => Make_Temporary (Loc, 'T'),
5639 Subtype_Indication =>
5640 Make_Subtype_Indication (Loc,
5641 Subtype_Mark =>
5642 New_Occurrence_Of (Etype (Base_Type (Typ)), Loc),
5643 Constraint =>
5644 Make_Index_Or_Discriminant_Constraint
5645 (Loc, Constraints)));
5647 Insert_Action (N, Decl);
5648 Prepend_Stored_Values (Base_Type (Typ));
5650 Set_Etype (N, Defining_Identifier (Decl));
5651 Set_Analyzed (N);
5653 Rewrite (N, Unchecked_Convert_To (Typ, N));
5654 Analyze (N);
5656 -- Case where we do not have fewer new discriminants than
5657 -- stored discriminants, so in this case we can simply use the
5658 -- stored discriminants of the subtype.
5660 else
5661 Prepend_Stored_Values (Typ);
5662 end if;
5663 end Generate_Aggregate_For_Derived_Type;
5664 end if;
5666 if Is_Tagged_Type (Typ) then
5668 -- In the tagged case, _parent and _tag component must be created
5670 -- Reset Null_Present unconditionally. Tagged records always have
5671 -- at least one field (the tag or the parent).
5673 Set_Null_Record_Present (N, False);
5675 -- When the current aggregate comes from the expansion of an
5676 -- extension aggregate, the parent expr is replaced by an
5677 -- aggregate formed by selected components of this expr.
5679 if Present (Parent_Expr)
5680 and then Is_Empty_List (Comps)
5681 then
5682 Comp := First_Component_Or_Discriminant (Typ);
5683 while Present (Comp) loop
5685 -- Skip all expander-generated components
5688 not Comes_From_Source (Original_Record_Component (Comp))
5689 then
5690 null;
5692 else
5693 New_Comp :=
5694 Make_Selected_Component (Loc,
5695 Prefix =>
5696 Unchecked_Convert_To (Typ,
5697 Duplicate_Subexpr (Parent_Expr, True)),
5699 Selector_Name => New_Occurrence_Of (Comp, Loc));
5701 Append_To (Comps,
5702 Make_Component_Association (Loc,
5703 Choices =>
5704 New_List (New_Occurrence_Of (Comp, Loc)),
5705 Expression =>
5706 New_Comp));
5708 Analyze_And_Resolve (New_Comp, Etype (Comp));
5709 end if;
5711 Next_Component_Or_Discriminant (Comp);
5712 end loop;
5713 end if;
5715 -- Compute the value for the Tag now, if the type is a root it
5716 -- will be included in the aggregate right away, otherwise it will
5717 -- be propagated to the parent aggregate.
5719 if Present (Orig_Tag) then
5720 Tag_Value := Orig_Tag;
5721 elsif not Tagged_Type_Expansion then
5722 Tag_Value := Empty;
5723 else
5724 Tag_Value :=
5725 New_Occurrence_Of
5726 (Node (First_Elmt (Access_Disp_Table (Typ))), Loc);
5727 end if;
5729 -- For a derived type, an aggregate for the parent is formed with
5730 -- all the inherited components.
5732 if Is_Derived_Type (Typ) then
5734 declare
5735 First_Comp : Node_Id;
5736 Parent_Comps : List_Id;
5737 Parent_Aggr : Node_Id;
5738 Parent_Name : Node_Id;
5740 begin
5741 -- Remove the inherited component association from the
5742 -- aggregate and store them in the parent aggregate
5744 First_Comp := First (Component_Associations (N));
5745 Parent_Comps := New_List;
5746 while Present (First_Comp)
5747 and then Scope (Original_Record_Component (
5748 Entity (First (Choices (First_Comp))))) /= Base_Typ
5749 loop
5750 Comp := First_Comp;
5751 Next (First_Comp);
5752 Remove (Comp);
5753 Append (Comp, Parent_Comps);
5754 end loop;
5756 Parent_Aggr := Make_Aggregate (Loc,
5757 Component_Associations => Parent_Comps);
5758 Set_Etype (Parent_Aggr, Etype (Base_Type (Typ)));
5760 -- Find the _parent component
5762 Comp := First_Component (Typ);
5763 while Chars (Comp) /= Name_uParent loop
5764 Comp := Next_Component (Comp);
5765 end loop;
5767 Parent_Name := New_Occurrence_Of (Comp, Loc);
5769 -- Insert the parent aggregate
5771 Prepend_To (Component_Associations (N),
5772 Make_Component_Association (Loc,
5773 Choices => New_List (Parent_Name),
5774 Expression => Parent_Aggr));
5776 -- Expand recursively the parent propagating the right Tag
5778 Expand_Record_Aggregate
5779 (Parent_Aggr, Tag_Value, Parent_Expr);
5781 -- The ancestor part may be a nested aggregate that has
5782 -- delayed expansion: recheck now.
5784 if Component_Not_OK_For_Backend then
5785 Convert_To_Assignments (N, Typ);
5786 end if;
5787 end;
5789 -- For a root type, the tag component is added (unless compiling
5790 -- for the VMs, where tags are implicit).
5792 elsif Tagged_Type_Expansion then
5793 declare
5794 Tag_Name : constant Node_Id :=
5795 New_Occurrence_Of
5796 (First_Tag_Component (Typ), Loc);
5797 Typ_Tag : constant Entity_Id := RTE (RE_Tag);
5798 Conv_Node : constant Node_Id :=
5799 Unchecked_Convert_To (Typ_Tag, Tag_Value);
5801 begin
5802 Set_Etype (Conv_Node, Typ_Tag);
5803 Prepend_To (Component_Associations (N),
5804 Make_Component_Association (Loc,
5805 Choices => New_List (Tag_Name),
5806 Expression => Conv_Node));
5807 end;
5808 end if;
5809 end if;
5810 end if;
5812 end Expand_Record_Aggregate;
5814 ----------------------------
5815 -- Has_Default_Init_Comps --
5816 ----------------------------
5818 function Has_Default_Init_Comps (N : Node_Id) return Boolean is
5819 Comps : constant List_Id := Component_Associations (N);
5820 C : Node_Id;
5821 Expr : Node_Id;
5822 begin
5823 pragma Assert (Nkind_In (N, N_Aggregate, N_Extension_Aggregate));
5825 if No (Comps) then
5826 return False;
5827 end if;
5829 if Has_Self_Reference (N) then
5830 return True;
5831 end if;
5833 -- Check if any direct component has default initialized components
5835 C := First (Comps);
5836 while Present (C) loop
5837 if Box_Present (C) then
5838 return True;
5839 end if;
5841 Next (C);
5842 end loop;
5844 -- Recursive call in case of aggregate expression
5846 C := First (Comps);
5847 while Present (C) loop
5848 Expr := Expression (C);
5850 if Present (Expr)
5851 and then
5852 Nkind_In (Expr, N_Aggregate, N_Extension_Aggregate)
5853 and then Has_Default_Init_Comps (Expr)
5854 then
5855 return True;
5856 end if;
5858 Next (C);
5859 end loop;
5861 return False;
5862 end Has_Default_Init_Comps;
5864 --------------------------
5865 -- Is_Delayed_Aggregate --
5866 --------------------------
5868 function Is_Delayed_Aggregate (N : Node_Id) return Boolean is
5869 Node : Node_Id := N;
5870 Kind : Node_Kind := Nkind (Node);
5872 begin
5873 if Kind = N_Qualified_Expression then
5874 Node := Expression (Node);
5875 Kind := Nkind (Node);
5876 end if;
5878 if Kind /= N_Aggregate and then Kind /= N_Extension_Aggregate then
5879 return False;
5880 else
5881 return Expansion_Delayed (Node);
5882 end if;
5883 end Is_Delayed_Aggregate;
5885 ----------------------------------------
5886 -- Is_Static_Dispatch_Table_Aggregate --
5887 ----------------------------------------
5889 function Is_Static_Dispatch_Table_Aggregate (N : Node_Id) return Boolean is
5890 Typ : constant Entity_Id := Base_Type (Etype (N));
5892 begin
5893 return Static_Dispatch_Tables
5894 and then Tagged_Type_Expansion
5895 and then RTU_Loaded (Ada_Tags)
5897 -- Avoid circularity when rebuilding the compiler
5899 and then Cunit_Entity (Get_Source_Unit (N)) /= RTU_Entity (Ada_Tags)
5900 and then (Typ = RTE (RE_Dispatch_Table_Wrapper)
5901 or else
5902 Typ = RTE (RE_Address_Array)
5903 or else
5904 Typ = RTE (RE_Type_Specific_Data)
5905 or else
5906 Typ = RTE (RE_Tag_Table)
5907 or else
5908 (RTE_Available (RE_Interface_Data)
5909 and then Typ = RTE (RE_Interface_Data))
5910 or else
5911 (RTE_Available (RE_Interfaces_Array)
5912 and then Typ = RTE (RE_Interfaces_Array))
5913 or else
5914 (RTE_Available (RE_Interface_Data_Element)
5915 and then Typ = RTE (RE_Interface_Data_Element)));
5916 end Is_Static_Dispatch_Table_Aggregate;
5918 -----------------------------
5919 -- Is_Two_Dim_Packed_Array --
5920 -----------------------------
5922 function Is_Two_Dim_Packed_Array (Typ : Entity_Id) return Boolean is
5923 C : constant Int := UI_To_Int (Component_Size (Typ));
5924 begin
5925 return Number_Dimensions (Typ) = 2
5926 and then Is_Bit_Packed_Array (Typ)
5927 and then
5928 (C = 1 or else C = 2 or else C = 4);
5929 end Is_Two_Dim_Packed_Array;
5931 --------------------
5932 -- Late_Expansion --
5933 --------------------
5935 function Late_Expansion
5936 (N : Node_Id;
5937 Typ : Entity_Id;
5938 Target : Node_Id) return List_Id
5940 begin
5941 if Is_Record_Type (Etype (N)) then
5942 return Build_Record_Aggr_Code (N, Typ, Target);
5944 else pragma Assert (Is_Array_Type (Etype (N)));
5945 return
5946 Build_Array_Aggr_Code
5947 (N => N,
5948 Ctype => Component_Type (Etype (N)),
5949 Index => First_Index (Typ),
5950 Into => Target,
5951 Scalar_Comp => Is_Scalar_Type (Component_Type (Typ)),
5952 Indexes => No_List);
5953 end if;
5954 end Late_Expansion;
5956 ----------------------------------
5957 -- Make_OK_Assignment_Statement --
5958 ----------------------------------
5960 function Make_OK_Assignment_Statement
5961 (Sloc : Source_Ptr;
5962 Name : Node_Id;
5963 Expression : Node_Id) return Node_Id
5965 begin
5966 Set_Assignment_OK (Name);
5968 return Make_Assignment_Statement (Sloc, Name, Expression);
5969 end Make_OK_Assignment_Statement;
5971 -----------------------
5972 -- Number_Of_Choices --
5973 -----------------------
5975 function Number_Of_Choices (N : Node_Id) return Nat is
5976 Assoc : Node_Id;
5977 Choice : Node_Id;
5979 Nb_Choices : Nat := 0;
5981 begin
5982 if Present (Expressions (N)) then
5983 return 0;
5984 end if;
5986 Assoc := First (Component_Associations (N));
5987 while Present (Assoc) loop
5988 Choice := First (Choices (Assoc));
5989 while Present (Choice) loop
5990 if Nkind (Choice) /= N_Others_Choice then
5991 Nb_Choices := Nb_Choices + 1;
5992 end if;
5994 Next (Choice);
5995 end loop;
5997 Next (Assoc);
5998 end loop;
6000 return Nb_Choices;
6001 end Number_Of_Choices;
6003 ------------------------------------
6004 -- Packed_Array_Aggregate_Handled --
6005 ------------------------------------
6007 -- The current version of this procedure will handle at compile time
6008 -- any array aggregate that meets these conditions:
6010 -- One and two dimensional, bit packed
6011 -- Underlying packed type is modular type
6012 -- Bounds are within 32-bit Int range
6013 -- All bounds and values are static
6015 -- Note: for now, in the 2-D case, we only handle component sizes of
6016 -- 1, 2, 4 (cases where an integral number of elements occupies a byte).
6018 function Packed_Array_Aggregate_Handled (N : Node_Id) return Boolean is
6019 Loc : constant Source_Ptr := Sloc (N);
6020 Typ : constant Entity_Id := Etype (N);
6021 Ctyp : constant Entity_Id := Component_Type (Typ);
6023 Not_Handled : exception;
6024 -- Exception raised if this aggregate cannot be handled
6026 begin
6027 -- Handle one- or two dimensional bit packed array
6029 if not Is_Bit_Packed_Array (Typ)
6030 or else Number_Dimensions (Typ) > 2
6031 then
6032 return False;
6033 end if;
6035 -- If two-dimensional, check whether it can be folded, and transformed
6036 -- into a one-dimensional aggregate for the Packed_Array_Type of the
6037 -- original type.
6039 if Number_Dimensions (Typ) = 2 then
6040 return Two_Dim_Packed_Array_Handled (N);
6041 end if;
6043 if not Is_Modular_Integer_Type (Packed_Array_Type (Typ)) then
6044 return False;
6045 end if;
6047 if not Is_Scalar_Type (Component_Type (Typ))
6048 and then Has_Non_Standard_Rep (Component_Type (Typ))
6049 then
6050 return False;
6051 end if;
6053 declare
6054 Csiz : constant Nat := UI_To_Int (Component_Size (Typ));
6056 Lo : Node_Id;
6057 Hi : Node_Id;
6058 -- Bounds of index type
6060 Lob : Uint;
6061 Hib : Uint;
6062 -- Values of bounds if compile time known
6064 function Get_Component_Val (N : Node_Id) return Uint;
6065 -- Given a expression value N of the component type Ctyp, returns a
6066 -- value of Csiz (component size) bits representing this value. If
6067 -- the value is non-static or any other reason exists why the value
6068 -- cannot be returned, then Not_Handled is raised.
6070 -----------------------
6071 -- Get_Component_Val --
6072 -----------------------
6074 function Get_Component_Val (N : Node_Id) return Uint is
6075 Val : Uint;
6077 begin
6078 -- We have to analyze the expression here before doing any further
6079 -- processing here. The analysis of such expressions is deferred
6080 -- till expansion to prevent some problems of premature analysis.
6082 Analyze_And_Resolve (N, Ctyp);
6084 -- Must have a compile time value. String literals have to be
6085 -- converted into temporaries as well, because they cannot easily
6086 -- be converted into their bit representation.
6088 if not Compile_Time_Known_Value (N)
6089 or else Nkind (N) = N_String_Literal
6090 then
6091 raise Not_Handled;
6092 end if;
6094 Val := Expr_Rep_Value (N);
6096 -- Adjust for bias, and strip proper number of bits
6098 if Has_Biased_Representation (Ctyp) then
6099 Val := Val - Expr_Value (Type_Low_Bound (Ctyp));
6100 end if;
6102 return Val mod Uint_2 ** Csiz;
6103 end Get_Component_Val;
6105 -- Here we know we have a one dimensional bit packed array
6107 begin
6108 Get_Index_Bounds (First_Index (Typ), Lo, Hi);
6110 -- Cannot do anything if bounds are dynamic
6112 if not Compile_Time_Known_Value (Lo)
6113 or else
6114 not Compile_Time_Known_Value (Hi)
6115 then
6116 return False;
6117 end if;
6119 -- Or are silly out of range of int bounds
6121 Lob := Expr_Value (Lo);
6122 Hib := Expr_Value (Hi);
6124 if not UI_Is_In_Int_Range (Lob)
6125 or else
6126 not UI_Is_In_Int_Range (Hib)
6127 then
6128 return False;
6129 end if;
6131 -- At this stage we have a suitable aggregate for handling at compile
6132 -- time. The only remaining checks are that the values of expressions
6133 -- in the aggregate are compile-time known (checks are performed by
6134 -- Get_Component_Val, and that any subtypes or ranges are statically
6135 -- known.
6137 -- If the aggregate is not fully positional at this stage, then
6138 -- convert it to positional form. Either this will fail, in which
6139 -- case we can do nothing, or it will succeed, in which case we have
6140 -- succeeded in handling the aggregate and transforming it into a
6141 -- modular value, or it will stay an aggregate, in which case we
6142 -- have failed to create a packed value for it.
6144 if Present (Component_Associations (N)) then
6145 Convert_To_Positional
6146 (N, Max_Others_Replicate => 64, Handle_Bit_Packed => True);
6147 return Nkind (N) /= N_Aggregate;
6148 end if;
6150 -- Otherwise we are all positional, so convert to proper value
6152 declare
6153 Lov : constant Int := UI_To_Int (Lob);
6154 Hiv : constant Int := UI_To_Int (Hib);
6156 Len : constant Nat := Int'Max (0, Hiv - Lov + 1);
6157 -- The length of the array (number of elements)
6159 Aggregate_Val : Uint;
6160 -- Value of aggregate. The value is set in the low order bits of
6161 -- this value. For the little-endian case, the values are stored
6162 -- from low-order to high-order and for the big-endian case the
6163 -- values are stored from high-order to low-order. Note that gigi
6164 -- will take care of the conversions to left justify the value in
6165 -- the big endian case (because of left justified modular type
6166 -- processing), so we do not have to worry about that here.
6168 Lit : Node_Id;
6169 -- Integer literal for resulting constructed value
6171 Shift : Nat;
6172 -- Shift count from low order for next value
6174 Incr : Int;
6175 -- Shift increment for loop
6177 Expr : Node_Id;
6178 -- Next expression from positional parameters of aggregate
6180 begin
6181 -- For little endian, we fill up the low order bits of the target
6182 -- value. For big endian we fill up the high order bits of the
6183 -- target value (which is a left justified modular value).
6185 -- Above comment needs extending for the code below, which is by
6186 -- the way incomprehensible, I have no idea what a xor b xor c
6187 -- means, and it hurts my brain to try to figure it out???
6188 -- Let's introduce a new variable, perhaps Effectively_Big_Endian
6189 -- and compute it with clearer code ???
6191 if Bytes_Big_Endian
6192 xor Debug_Flag_8
6193 xor Reverse_Storage_Order (Base_Type (Typ))
6194 then
6195 Shift := Csiz * (Len - 1);
6196 Incr := -Csiz;
6197 else
6198 Shift := 0;
6199 Incr := +Csiz;
6200 end if;
6202 -- Loop to set the values
6204 if Len = 0 then
6205 Aggregate_Val := Uint_0;
6206 else
6207 Expr := First (Expressions (N));
6208 Aggregate_Val := Get_Component_Val (Expr) * Uint_2 ** Shift;
6210 for J in 2 .. Len loop
6211 Shift := Shift + Incr;
6212 Next (Expr);
6213 Aggregate_Val :=
6214 Aggregate_Val + Get_Component_Val (Expr) * Uint_2 ** Shift;
6215 end loop;
6216 end if;
6218 -- Now we can rewrite with the proper value
6220 Lit := Make_Integer_Literal (Loc, Intval => Aggregate_Val);
6221 Set_Print_In_Hex (Lit);
6223 -- Construct the expression using this literal. Note that it is
6224 -- important to qualify the literal with its proper modular type
6225 -- since universal integer does not have the required range and
6226 -- also this is a left justified modular type, which is important
6227 -- in the big-endian case.
6229 Rewrite (N,
6230 Unchecked_Convert_To (Typ,
6231 Make_Qualified_Expression (Loc,
6232 Subtype_Mark =>
6233 New_Occurrence_Of (Packed_Array_Type (Typ), Loc),
6234 Expression => Lit)));
6236 Analyze_And_Resolve (N, Typ);
6237 return True;
6238 end;
6239 end;
6241 exception
6242 when Not_Handled =>
6243 return False;
6244 end Packed_Array_Aggregate_Handled;
6246 ----------------------------
6247 -- Has_Mutable_Components --
6248 ----------------------------
6250 function Has_Mutable_Components (Typ : Entity_Id) return Boolean is
6251 Comp : Entity_Id;
6253 begin
6254 Comp := First_Component (Typ);
6255 while Present (Comp) loop
6256 if Is_Record_Type (Etype (Comp))
6257 and then Has_Discriminants (Etype (Comp))
6258 and then not Is_Constrained (Etype (Comp))
6259 then
6260 return True;
6261 end if;
6263 Next_Component (Comp);
6264 end loop;
6266 return False;
6267 end Has_Mutable_Components;
6269 ------------------------------
6270 -- Initialize_Discriminants --
6271 ------------------------------
6273 procedure Initialize_Discriminants (N : Node_Id; Typ : Entity_Id) is
6274 Loc : constant Source_Ptr := Sloc (N);
6275 Bas : constant Entity_Id := Base_Type (Typ);
6276 Par : constant Entity_Id := Etype (Bas);
6277 Decl : constant Node_Id := Parent (Par);
6278 Ref : Node_Id;
6280 begin
6281 if Is_Tagged_Type (Bas)
6282 and then Is_Derived_Type (Bas)
6283 and then Has_Discriminants (Par)
6284 and then Has_Discriminants (Bas)
6285 and then Number_Discriminants (Bas) /= Number_Discriminants (Par)
6286 and then Nkind (Decl) = N_Full_Type_Declaration
6287 and then Nkind (Type_Definition (Decl)) = N_Record_Definition
6288 and then Present
6289 (Variant_Part (Component_List (Type_Definition (Decl))))
6290 and then Nkind (N) /= N_Extension_Aggregate
6291 then
6293 -- Call init proc to set discriminants.
6294 -- There should eventually be a special procedure for this ???
6296 Ref := New_Reference_To (Defining_Identifier (N), Loc);
6297 Insert_Actions_After (N,
6298 Build_Initialization_Call (Sloc (N), Ref, Typ));
6299 end if;
6300 end Initialize_Discriminants;
6302 ----------------
6303 -- Must_Slide --
6304 ----------------
6306 function Must_Slide
6307 (Obj_Type : Entity_Id;
6308 Typ : Entity_Id) return Boolean
6310 L1, L2, H1, H2 : Node_Id;
6311 begin
6312 -- No sliding if the type of the object is not established yet, if it is
6313 -- an unconstrained type whose actual subtype comes from the aggregate,
6314 -- or if the two types are identical.
6316 if not Is_Array_Type (Obj_Type) then
6317 return False;
6319 elsif not Is_Constrained (Obj_Type) then
6320 return False;
6322 elsif Typ = Obj_Type then
6323 return False;
6325 else
6326 -- Sliding can only occur along the first dimension
6328 Get_Index_Bounds (First_Index (Typ), L1, H1);
6329 Get_Index_Bounds (First_Index (Obj_Type), L2, H2);
6331 if not Is_Static_Expression (L1)
6332 or else not Is_Static_Expression (L2)
6333 or else not Is_Static_Expression (H1)
6334 or else not Is_Static_Expression (H2)
6335 then
6336 return False;
6337 else
6338 return Expr_Value (L1) /= Expr_Value (L2)
6339 or else
6340 Expr_Value (H1) /= Expr_Value (H2);
6341 end if;
6342 end if;
6343 end Must_Slide;
6345 ---------------------------
6346 -- Safe_Slice_Assignment --
6347 ---------------------------
6349 function Safe_Slice_Assignment (N : Node_Id) return Boolean is
6350 Loc : constant Source_Ptr := Sloc (Parent (N));
6351 Pref : constant Node_Id := Prefix (Name (Parent (N)));
6352 Range_Node : constant Node_Id := Discrete_Range (Name (Parent (N)));
6353 Expr : Node_Id;
6354 L_J : Entity_Id;
6355 L_Iter : Node_Id;
6356 L_Body : Node_Id;
6357 Stat : Node_Id;
6359 begin
6360 -- Generate: for J in Range loop Pref (J) := Expr; end loop;
6362 if Comes_From_Source (N)
6363 and then No (Expressions (N))
6364 and then Nkind (First (Choices (First (Component_Associations (N)))))
6365 = N_Others_Choice
6366 then
6367 Expr := Expression (First (Component_Associations (N)));
6368 L_J := Make_Temporary (Loc, 'J');
6370 L_Iter :=
6371 Make_Iteration_Scheme (Loc,
6372 Loop_Parameter_Specification =>
6373 Make_Loop_Parameter_Specification
6374 (Loc,
6375 Defining_Identifier => L_J,
6376 Discrete_Subtype_Definition => Relocate_Node (Range_Node)));
6378 L_Body :=
6379 Make_Assignment_Statement (Loc,
6380 Name =>
6381 Make_Indexed_Component (Loc,
6382 Prefix => Relocate_Node (Pref),
6383 Expressions => New_List (New_Occurrence_Of (L_J, Loc))),
6384 Expression => Relocate_Node (Expr));
6386 -- Construct the final loop
6388 Stat :=
6389 Make_Implicit_Loop_Statement
6390 (Node => Parent (N),
6391 Identifier => Empty,
6392 Iteration_Scheme => L_Iter,
6393 Statements => New_List (L_Body));
6395 -- Set type of aggregate to be type of lhs in assignment,
6396 -- to suppress redundant length checks.
6398 Set_Etype (N, Etype (Name (Parent (N))));
6400 Rewrite (Parent (N), Stat);
6401 Analyze (Parent (N));
6402 return True;
6404 else
6405 return False;
6406 end if;
6407 end Safe_Slice_Assignment;
6409 ----------------------------------
6410 -- Two_Dim_Packed_Array_Handled --
6411 ----------------------------------
6413 function Two_Dim_Packed_Array_Handled (N : Node_Id) return Boolean is
6414 Loc : constant Source_Ptr := Sloc (N);
6415 Typ : constant Entity_Id := Etype (N);
6416 Ctyp : constant Entity_Id := Component_Type (Typ);
6417 Comp_Size : constant Int := UI_To_Int (Component_Size (Typ));
6418 Packed_Array : constant Entity_Id := Packed_Array_Type (Base_Type (Typ));
6420 One_Comp : Node_Id;
6421 -- Expression in original aggregate
6423 One_Dim : Node_Id;
6424 -- One-dimensional subaggregate
6426 begin
6428 -- For now, only deal with cases where an integral number of elements
6429 -- fit in a single byte. This includes the most common boolean case.
6431 if not (Comp_Size = 1 or else
6432 Comp_Size = 2 or else
6433 Comp_Size = 4)
6434 then
6435 return False;
6436 end if;
6438 Convert_To_Positional
6439 (N, Max_Others_Replicate => 64, Handle_Bit_Packed => True);
6441 -- Verify that all components are static
6443 if Nkind (N) = N_Aggregate
6444 and then Compile_Time_Known_Aggregate (N)
6445 then
6446 null;
6448 -- The aggregate may have been re-analyzed and converted already
6450 elsif Nkind (N) /= N_Aggregate then
6451 return True;
6453 -- If component associations remain, the aggregate is not static
6455 elsif Present (Component_Associations (N)) then
6456 return False;
6458 else
6459 One_Dim := First (Expressions (N));
6460 while Present (One_Dim) loop
6461 if Present (Component_Associations (One_Dim)) then
6462 return False;
6463 end if;
6465 One_Comp := First (Expressions (One_Dim));
6466 while Present (One_Comp) loop
6467 if not Is_OK_Static_Expression (One_Comp) then
6468 return False;
6469 end if;
6471 Next (One_Comp);
6472 end loop;
6474 Next (One_Dim);
6475 end loop;
6476 end if;
6478 -- Two-dimensional aggregate is now fully positional so pack one
6479 -- dimension to create a static one-dimensional array, and rewrite
6480 -- as an unchecked conversion to the original type.
6482 declare
6483 Byte_Size : constant Int := UI_To_Int (Component_Size (Packed_Array));
6484 -- The packed array type is a byte array
6486 Packed_Num : Int;
6487 -- Number of components accumulated in current byte
6489 Comps : List_Id;
6490 -- Assembled list of packed values for equivalent aggregate
6492 Comp_Val : Uint;
6493 -- integer value of component
6495 Incr : Int;
6496 -- Step size for packing
6498 Init_Shift : Int;
6499 -- Endian-dependent start position for packing
6501 Shift : Int;
6502 -- Current insertion position
6504 Val : Int;
6505 -- Component of packed array being assembled.
6507 begin
6508 Comps := New_List;
6509 Val := 0;
6510 Packed_Num := 0;
6512 -- Account for endianness. See corresponding comment in
6513 -- Packed_Array_Aggregate_Handled concerning the following.
6515 if Bytes_Big_Endian
6516 xor Debug_Flag_8
6517 xor Reverse_Storage_Order (Base_Type (Typ))
6518 then
6519 Init_Shift := Byte_Size - Comp_Size;
6520 Incr := -Comp_Size;
6521 else
6522 Init_Shift := 0;
6523 Incr := +Comp_Size;
6524 end if;
6526 Shift := Init_Shift;
6527 One_Dim := First (Expressions (N));
6529 -- Iterate over each subaggregate
6531 while Present (One_Dim) loop
6532 One_Comp := First (Expressions (One_Dim));
6534 while Present (One_Comp) loop
6535 if Packed_Num = Byte_Size / Comp_Size then
6537 -- Byte is complete, add to list of expressions
6539 Append (Make_Integer_Literal (Sloc (One_Dim), Val), Comps);
6540 Val := 0;
6541 Shift := Init_Shift;
6542 Packed_Num := 0;
6544 else
6545 Comp_Val := Expr_Rep_Value (One_Comp);
6547 -- Adjust for bias, and strip proper number of bits
6549 if Has_Biased_Representation (Ctyp) then
6550 Comp_Val := Comp_Val - Expr_Value (Type_Low_Bound (Ctyp));
6551 end if;
6553 Comp_Val := Comp_Val mod Uint_2 ** Comp_Size;
6554 Val := UI_To_Int (Val + Comp_Val * Uint_2 ** Shift);
6555 Shift := Shift + Incr;
6556 One_Comp := Next (One_Comp);
6557 Packed_Num := Packed_Num + 1;
6558 end if;
6559 end loop;
6561 One_Dim := Next (One_Dim);
6562 end loop;
6564 if Packed_Num > 0 then
6566 -- Add final incomplete byte if present
6568 Append (Make_Integer_Literal (Sloc (One_Dim), Val), Comps);
6569 end if;
6571 Rewrite (N,
6572 Unchecked_Convert_To (Typ,
6573 Make_Qualified_Expression (Loc,
6574 Subtype_Mark => New_Occurrence_Of (Packed_Array, Loc),
6575 Expression =>
6576 Make_Aggregate (Loc, Expressions => Comps))));
6577 Analyze_And_Resolve (N);
6578 return True;
6579 end;
6580 end Two_Dim_Packed_Array_Handled;
6582 ---------------------
6583 -- Sort_Case_Table --
6584 ---------------------
6586 procedure Sort_Case_Table (Case_Table : in out Case_Table_Type) is
6587 L : constant Int := Case_Table'First;
6588 U : constant Int := Case_Table'Last;
6589 K : Int;
6590 J : Int;
6591 T : Case_Bounds;
6593 begin
6594 K := L;
6595 while K /= U loop
6596 T := Case_Table (K + 1);
6598 J := K + 1;
6599 while J /= L
6600 and then Expr_Value (Case_Table (J - 1).Choice_Lo) >
6601 Expr_Value (T.Choice_Lo)
6602 loop
6603 Case_Table (J) := Case_Table (J - 1);
6604 J := J - 1;
6605 end loop;
6607 Case_Table (J) := T;
6608 K := K + 1;
6609 end loop;
6610 end Sort_Case_Table;
6612 ----------------------------
6613 -- Static_Array_Aggregate --
6614 ----------------------------
6616 function Static_Array_Aggregate (N : Node_Id) return Boolean is
6617 Bounds : constant Node_Id := Aggregate_Bounds (N);
6619 Typ : constant Entity_Id := Etype (N);
6620 Comp_Type : constant Entity_Id := Component_Type (Typ);
6621 Agg : Node_Id;
6622 Expr : Node_Id;
6623 Lo : Node_Id;
6624 Hi : Node_Id;
6626 begin
6627 if Is_Tagged_Type (Typ)
6628 or else Is_Controlled (Typ)
6629 or else Is_Packed (Typ)
6630 then
6631 return False;
6632 end if;
6634 if Present (Bounds)
6635 and then Nkind (Bounds) = N_Range
6636 and then Nkind (Low_Bound (Bounds)) = N_Integer_Literal
6637 and then Nkind (High_Bound (Bounds)) = N_Integer_Literal
6638 then
6639 Lo := Low_Bound (Bounds);
6640 Hi := High_Bound (Bounds);
6642 if No (Component_Associations (N)) then
6644 -- Verify that all components are static integers
6646 Expr := First (Expressions (N));
6647 while Present (Expr) loop
6648 if Nkind (Expr) /= N_Integer_Literal then
6649 return False;
6650 end if;
6652 Next (Expr);
6653 end loop;
6655 return True;
6657 else
6658 -- We allow only a single named association, either a static
6659 -- range or an others_clause, with a static expression.
6661 Expr := First (Component_Associations (N));
6663 if Present (Expressions (N)) then
6664 return False;
6666 elsif Present (Next (Expr)) then
6667 return False;
6669 elsif Present (Next (First (Choices (Expr)))) then
6670 return False;
6672 else
6673 -- The aggregate is static if all components are literals,
6674 -- or else all its components are static aggregates for the
6675 -- component type. We also limit the size of a static aggregate
6676 -- to prevent runaway static expressions.
6678 if Is_Array_Type (Comp_Type)
6679 or else Is_Record_Type (Comp_Type)
6680 then
6681 if Nkind (Expression (Expr)) /= N_Aggregate
6682 or else
6683 not Compile_Time_Known_Aggregate (Expression (Expr))
6684 then
6685 return False;
6686 end if;
6688 elsif Nkind (Expression (Expr)) /= N_Integer_Literal then
6689 return False;
6690 end if;
6692 if not Aggr_Size_OK (N, Typ) then
6693 return False;
6694 end if;
6696 -- Create a positional aggregate with the right number of
6697 -- copies of the expression.
6699 Agg := Make_Aggregate (Sloc (N), New_List, No_List);
6701 for I in UI_To_Int (Intval (Lo)) .. UI_To_Int (Intval (Hi))
6702 loop
6703 Append_To
6704 (Expressions (Agg), New_Copy (Expression (Expr)));
6706 -- The copied expression must be analyzed and resolved.
6707 -- Besides setting the type, this ensures that static
6708 -- expressions are appropriately marked as such.
6710 Analyze_And_Resolve
6711 (Last (Expressions (Agg)), Component_Type (Typ));
6712 end loop;
6714 Set_Aggregate_Bounds (Agg, Bounds);
6715 Set_Etype (Agg, Typ);
6716 Set_Analyzed (Agg);
6717 Rewrite (N, Agg);
6718 Set_Compile_Time_Known_Aggregate (N);
6720 return True;
6721 end if;
6722 end if;
6724 else
6725 return False;
6726 end if;
6727 end Static_Array_Aggregate;
6729 end Exp_Aggr;