OSDN Git Service

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