OSDN Git Service

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