OSDN Git Service

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