OSDN Git Service

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