OSDN Git Service

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