OSDN Git Service

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