OSDN Git Service

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