OSDN Git Service

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