OSDN Git Service

Add Fariborz to my last change.
[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-2004 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 2,  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 COPYING.  If not, write --
19 -- to  the Free Software Foundation,  59 Temple Place - Suite 330,  Boston, --
20 -- MA 02111-1307, USA.                                                      --
21 --                                                                          --
22 -- GNAT was originally developed  by the GNAT team at  New York University. --
23 -- Extensive contributions were provided by Ada Core Technologies Inc.      --
24 --                                                                          --
25 ------------------------------------------------------------------------------
26
27 with Atree;    use Atree;
28 with Checks;   use Checks;
29 with Debug;    use Debug;
30 with Einfo;    use Einfo;
31 with Elists;   use Elists;
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 Hostparm; use Hostparm;
40 with Itypes;   use Itypes;
41 with Lib;      use Lib;
42 with Nmake;    use Nmake;
43 with Nlists;   use Nlists;
44 with Restrict; use Restrict;
45 with Rident;   use Rident;
46 with Rtsfind;  use Rtsfind;
47 with Ttypes;   use Ttypes;
48 with Sem;      use Sem;
49 with Sem_Ch3;  use Sem_Ch3;
50 with Sem_Eval; use Sem_Eval;
51 with Sem_Res;  use Sem_Res;
52 with Sem_Util; use Sem_Util;
53 with Sinfo;    use Sinfo;
54 with Snames;   use Snames;
55 with Stand;    use Stand;
56 with Tbuild;   use Tbuild;
57 with Uintp;    use Uintp;
58
59 package body Exp_Aggr is
60
61    type Case_Bounds is record
62      Choice_Lo   : Node_Id;
63      Choice_Hi   : Node_Id;
64      Choice_Node : Node_Id;
65    end record;
66
67    type Case_Table_Type is array (Nat range <>) of Case_Bounds;
68    --  Table type used by Check_Case_Choices procedure
69
70    procedure Sort_Case_Table (Case_Table : in out Case_Table_Type);
71    --  Sort the Case Table using the Lower Bound of each Choice as the key.
72    --  A simple insertion sort is used since the number of choices in a case
73    --  statement of variant part will usually be small and probably in near
74    --  sorted order.
75
76    function Has_Default_Init_Comps (N : Node_Id) return Boolean;
77    --  N is an aggregate (record or array). Checks the presence of default
78    --  initialization (<>) in any component (Ada 2005: AI-287)
79
80    ------------------------------------------------------
81    -- Local subprograms for Record Aggregate Expansion --
82    ------------------------------------------------------
83
84    procedure Expand_Record_Aggregate
85      (N           : Node_Id;
86       Orig_Tag    : Node_Id := Empty;
87       Parent_Expr : Node_Id := Empty);
88    --  This is the top level procedure for record aggregate expansion.
89    --  Expansion for record aggregates needs expand aggregates for tagged
90    --  record types. Specifically Expand_Record_Aggregate adds the Tag
91    --  field in front of the Component_Association list that was created
92    --  during resolution by Resolve_Record_Aggregate.
93    --
94    --    N is the record aggregate node.
95    --    Orig_Tag is the value of the Tag that has to be provided for this
96    --      specific aggregate. It carries the tag corresponding to the type
97    --      of the outermost aggregate during the recursive expansion
98    --    Parent_Expr is the ancestor part of the original extension
99    --      aggregate
100
101    procedure Convert_To_Assignments (N : Node_Id; Typ : Entity_Id);
102    --  N is an N_Aggregate of a N_Extension_Aggregate. Typ is the type of
103    --  the aggregate. Transform the given aggregate into a sequence of
104    --  assignments component per component.
105
106    function Build_Record_Aggr_Code
107      (N                             : Node_Id;
108       Typ                           : Entity_Id;
109       Target                        : Node_Id;
110       Flist                         : Node_Id   := Empty;
111       Obj                           : Entity_Id := Empty;
112       Is_Limited_Ancestor_Expansion : Boolean   := False) return List_Id;
113    --  N is an N_Aggregate or a N_Extension_Aggregate. Typ is the type
114    --  of the aggregate. Target is an expression containing the
115    --  location on which the component by component assignments will
116    --  take place. Returns the list of assignments plus all other
117    --  adjustments needed for tagged and controlled types. Flist is an
118    --  expression representing the finalization list on which to
119    --  attach the controlled components if any. Obj is present in the
120    --  object declaration and dynamic allocation cases, it contains
121    --  an entity that allows to know if the value being created needs to be
122    --  attached to the final list in case of pragma finalize_Storage_Only.
123    --  Is_Limited_Ancestor_Expansion indicates that the function has been
124    --  called recursively to expand the limited ancestor to avoid copying it.
125
126    function Has_Mutable_Components (Typ : Entity_Id) return Boolean;
127    --  Return true if one of the component is of a discriminated type with
128    --  defaults. An aggregate for a type with mutable components must be
129    --  expanded into individual assignments.
130
131    procedure Initialize_Discriminants (N : Node_Id; Typ : Entity_Id);
132    --  If the type of the aggregate is a type extension with renamed discrimi-
133    --  nants, we must initialize the hidden discriminants of the parent.
134    --  Otherwise, the target object must not be initialized. The discriminants
135    --  are initialized by calling the initialization procedure for the type.
136    --  This is incorrect if the initialization of other components has any
137    --  side effects. We restrict this call to the case where the parent type
138    --  has a variant part, because this is the only case where the hidden
139    --  discriminants are accessed, namely when calling discriminant checking
140    --  functions of the parent type, and when applying a stream attribute to
141    --  an object of the derived type.
142
143    -----------------------------------------------------
144    -- Local Subprograms for Array Aggregate Expansion --
145    -----------------------------------------------------
146
147    procedure Convert_To_Positional
148      (N                    : Node_Id;
149       Max_Others_Replicate : Nat     := 5;
150       Handle_Bit_Packed    : Boolean := False);
151    --  If possible, convert named notation to positional notation. This
152    --  conversion is possible only in some static cases. If the conversion
153    --  is possible, then N is rewritten with the analyzed converted
154    --  aggregate. The parameter Max_Others_Replicate controls the maximum
155    --  number of values corresponding to an others choice that will be
156    --  converted to positional notation (the default of 5 is the normal
157    --  limit, and reflects the fact that normally the loop is better than
158    --  a lot of separate assignments). Note that this limit gets overridden
159    --  in any case if either of the restrictions No_Elaboration_Code or
160    --  No_Implicit_Loops is set. The parameter Handle_Bit_Packed is usually
161    --  set False (since we do not expect the back end to handle bit packed
162    --  arrays, so the normal case of conversion is pointless), but in the
163    --  special case of a call from Packed_Array_Aggregate_Handled, we set
164    --  this parameter to True, since these are cases we handle in there.
165
166    procedure Expand_Array_Aggregate (N : Node_Id);
167    --  This is the top-level routine to perform array aggregate expansion.
168    --  N is the N_Aggregate node to be expanded.
169
170    function Backend_Processing_Possible (N : Node_Id) return Boolean;
171    --  This function checks if array aggregate N can be processed directly
172    --  by Gigi. If this is the case True is returned.
173
174    function Build_Array_Aggr_Code
175      (N           : Node_Id;
176       Ctype       : Entity_Id;
177       Index       : Node_Id;
178       Into        : Node_Id;
179       Scalar_Comp : Boolean;
180       Indices     : List_Id := No_List;
181       Flist       : Node_Id := Empty) return List_Id;
182    --  This recursive routine returns a list of statements containing the
183    --  loops and assignments that are needed for the expansion of the array
184    --  aggregate N.
185    --
186    --    N is the (sub-)aggregate node to be expanded into code. This node
187    --    has been fully analyzed, and its Etype is properly set.
188    --
189    --    Index is the index node corresponding to the array sub-aggregate N.
190    --
191    --    Into is the target expression into which we are copying the aggregate.
192    --    Note that this node may not have been analyzed yet, and so the Etype
193    --    field may not be set.
194    --
195    --    Scalar_Comp is True if the component type of the aggregate is scalar.
196    --
197    --    Indices is the current list of expressions used to index the
198    --    object we are writing into.
199    --
200    --    Flist is an expression representing the finalization list on which
201    --    to attach the controlled components if any.
202
203    function Number_Of_Choices (N : Node_Id) return Nat;
204    --  Returns the number of discrete choices (not including the others choice
205    --  if present) contained in (sub-)aggregate N.
206
207    function Late_Expansion
208      (N      : Node_Id;
209       Typ    : Entity_Id;
210       Target : Node_Id;
211       Flist  : Node_Id := Empty;
212       Obj    : Entity_Id := Empty) return List_Id;
213    --  N is a nested (record or array) aggregate that has been marked
214    --  with 'Delay_Expansion'. Typ is the expected type of the
215    --  aggregate and Target is a (duplicable) expression that will
216    --  hold the result of the aggregate expansion. Flist is the
217    --  finalization list to be used to attach controlled
218    --  components. 'Obj' when non empty, carries the original object
219    --  being initialized in order to know if it needs to be attached
220    --  to the previous parameter which may not be the case when
221    --  Finalize_Storage_Only is set.  Basically this procedure is used
222    --  to implement top-down expansions of nested aggregates. This is
223    --  necessary for avoiding temporaries at each level as well as for
224    --  propagating the right internal finalization list.
225
226    function Make_OK_Assignment_Statement
227      (Sloc       : Source_Ptr;
228       Name       : Node_Id;
229       Expression : Node_Id) return Node_Id;
230    --  This is like Make_Assignment_Statement, except that Assignment_OK
231    --  is set in the left operand. All assignments built by this unit
232    --  use this routine. This is needed to deal with assignments to
233    --  initialized constants that are done in place.
234
235    function Packed_Array_Aggregate_Handled (N : Node_Id) return Boolean;
236    --  Given an array aggregate, this function handles the case of a packed
237    --  array aggregate with all constant values, where the aggregate can be
238    --  evaluated at compile time. If this is possible, then N is rewritten
239    --  to be its proper compile time value with all the components properly
240    --  assembled. The expression is analyzed and resolved and True is
241    --  returned. If this transformation is not possible, N is unchanged
242    --  and False is returned
243
244    function Safe_Slice_Assignment (N : Node_Id) return Boolean;
245    --  If a slice assignment has an aggregate with a single others_choice,
246    --  the assignment can be done in place even if bounds are not static,
247    --  by converting it into a loop over the discrete range of the slice.
248
249    ---------------------------------
250    -- Backend_Processing_Possible --
251    ---------------------------------
252
253    --  Backend processing by Gigi/gcc is possible only if all the following
254    --  conditions are met:
255
256    --    1. N is fully positional
257
258    --    2. N is not a bit-packed array aggregate;
259
260    --    3. The size of N's array type must be known at compile time. Note
261    --       that this implies that the component size is also known
262
263    --    4. The array type of N does not follow the Fortran layout convention
264    --       or if it does it must be 1 dimensional.
265
266    --    5. The array component type is tagged, which may necessitate
267    --       reassignment of proper tags.
268
269    --    6. The array component type might have unaligned bit components
270
271    function Backend_Processing_Possible (N : Node_Id) return Boolean is
272       Typ : constant Entity_Id := Etype (N);
273       --  Typ is the correct constrained array subtype of the aggregate.
274
275       function Static_Check (N : Node_Id; Index : Node_Id) return Boolean;
276       --  Recursively checks that N is fully positional, returns true if so.
277
278       ------------------
279       -- Static_Check --
280       ------------------
281
282       function Static_Check (N : Node_Id; Index : Node_Id) return Boolean is
283          Expr : Node_Id;
284
285       begin
286          --  Check for component associations
287
288          if Present (Component_Associations (N)) then
289             return False;
290          end if;
291
292          --  Recurse to check subaggregates, which may appear in qualified
293          --  expressions. If delayed, the front-end will have to expand.
294
295          Expr := First (Expressions (N));
296
297          while Present (Expr) loop
298
299             if Is_Delayed_Aggregate (Expr) then
300                return False;
301             end if;
302
303             if Present (Next_Index (Index))
304                and then not Static_Check (Expr, Next_Index (Index))
305             then
306                return False;
307             end if;
308
309             Next (Expr);
310          end loop;
311
312          return True;
313       end Static_Check;
314
315    --  Start of processing for Backend_Processing_Possible
316
317    begin
318       --  Checks 2 (array must not be bit packed)
319
320       if Is_Bit_Packed_Array (Typ) then
321          return False;
322       end if;
323
324       --  Checks 4 (array must not be multi-dimensional Fortran case)
325
326       if Convention (Typ) = Convention_Fortran
327         and then Number_Dimensions (Typ) > 1
328       then
329          return False;
330       end if;
331
332       --  Checks 3 (size of array must be known at compile time)
333
334       if not Size_Known_At_Compile_Time (Typ) then
335          return False;
336       end if;
337
338       --  Checks 1 (aggregate must be fully positional)
339
340       if not Static_Check (N, First_Index (Typ)) then
341          return False;
342       end if;
343
344       --  Checks 5 (if the component type is tagged, then we may need
345       --    to do tag adjustments; perhaps this should be refined to
346       --    check for any component associations that actually
347       --    need tag adjustment, along the lines of the test that's
348       --    done in Has_Delayed_Nested_Aggregate_Or_Tagged_Comps
349       --    for record aggregates with tagged components, but not
350       --    clear whether it's worthwhile ???; in the case of the
351       --    JVM, object tags are handled implicitly)
352
353       if Is_Tagged_Type (Component_Type (Typ)) and then not Java_VM then
354          return False;
355       end if;
356
357       --  Checks 6 (component type must not have bit aligned components)
358
359       if Type_May_Have_Bit_Aligned_Components (Component_Type (Typ)) then
360          return False;
361       end if;
362
363       --  Backend processing is possible
364
365       Set_Compile_Time_Known_Aggregate (N, True);
366       Set_Size_Known_At_Compile_Time (Etype (N), True);
367       return True;
368    end Backend_Processing_Possible;
369
370    ---------------------------
371    -- Build_Array_Aggr_Code --
372    ---------------------------
373
374    --  The code that we generate from a one dimensional aggregate is
375
376    --  1. If the sub-aggregate contains discrete choices we
377
378    --     (a) Sort the discrete choices
379
380    --     (b) Otherwise for each discrete choice that specifies a range we
381    --         emit a loop. If a range specifies a maximum of three values, or
382    --         we are dealing with an expression we emit a sequence of
383    --         assignments instead of a loop.
384
385    --     (c) Generate the remaining loops to cover the others choice if any.
386
387    --  2. If the aggregate contains positional elements we
388
389    --     (a) translate the positional elements in a series of assignments.
390
391    --     (b) Generate a final loop to cover the others choice if any.
392    --         Note that this final loop has to be a while loop since the case
393
394    --             L : Integer := Integer'Last;
395    --             H : Integer := Integer'Last;
396    --             A : array (L .. H) := (1, others =>0);
397
398    --         cannot be handled by a for loop. Thus for the following
399
400    --             array (L .. H) := (.. positional elements.., others =>E);
401
402    --         we always generate something like:
403
404    --             J : Index_Type := Index_Of_Last_Positional_Element;
405    --             while J < H loop
406    --                J := Index_Base'Succ (J)
407    --                Tmp (J) := E;
408    --             end loop;
409
410    function Build_Array_Aggr_Code
411      (N           : Node_Id;
412       Ctype       : Entity_Id;
413       Index       : Node_Id;
414       Into        : Node_Id;
415       Scalar_Comp : Boolean;
416       Indices     : List_Id := No_List;
417       Flist       : Node_Id := Empty) return List_Id
418    is
419       Loc          : constant Source_Ptr := Sloc (N);
420       Index_Base   : constant Entity_Id  := Base_Type (Etype (Index));
421       Index_Base_L : constant Node_Id := Type_Low_Bound (Index_Base);
422       Index_Base_H : constant Node_Id := Type_High_Bound (Index_Base);
423
424       function Add (Val : Int; To : Node_Id) return Node_Id;
425       --  Returns an expression where Val is added to expression To,
426       --  unless To+Val is provably out of To's base type range.
427       --  To must be an already analyzed expression.
428
429       function Empty_Range (L, H : Node_Id) return Boolean;
430       --  Returns True if the range defined by L .. H is certainly empty.
431
432       function Equal (L, H : Node_Id) return Boolean;
433       --  Returns True if L = H for sure.
434
435       function Index_Base_Name return Node_Id;
436       --  Returns a new reference to the index type name.
437
438       function Gen_Assign (Ind : Node_Id; Expr : Node_Id) return List_Id;
439       --  Ind must be a side-effect free expression. If the input aggregate
440       --  N to Build_Loop contains no sub-aggregates, then this function
441       --  returns the assignment statement:
442       --
443       --     Into (Indices, Ind) := Expr;
444       --
445       --  Otherwise we call Build_Code recursively.
446       --
447       --  Ada 2005 (AI-287): In case of default initialized component, Expr
448       --  is empty and we generate a call to the corresponding IP subprogram.
449
450       function Gen_Loop (L, H : Node_Id; Expr : Node_Id) return List_Id;
451       --  Nodes L and H must be side-effect free expressions.
452       --  If the input aggregate N to Build_Loop contains no sub-aggregates,
453       --  This routine returns the for loop statement
454       --
455       --     for J in Index_Base'(L) .. Index_Base'(H) loop
456       --        Into (Indices, J) := Expr;
457       --     end loop;
458       --
459       --  Otherwise we call Build_Code recursively.
460       --  As an optimization if the loop covers 3 or less scalar elements we
461       --  generate a sequence of assignments.
462
463       function Gen_While (L, H : Node_Id; Expr : Node_Id) return List_Id;
464       --  Nodes L and H must be side-effect free expressions.
465       --  If the input aggregate N to Build_Loop contains no sub-aggregates,
466       --  This routine returns the while loop statement
467       --
468       --     J : Index_Base := L;
469       --     while J < H loop
470       --        J := Index_Base'Succ (J);
471       --        Into (Indices, J) := Expr;
472       --     end loop;
473       --
474       --  Otherwise we call Build_Code recursively
475
476       function Local_Compile_Time_Known_Value (E : Node_Id) return Boolean;
477       function Local_Expr_Value               (E : Node_Id) return Uint;
478       --  These two Local routines are used to replace the corresponding ones
479       --  in sem_eval because while processing the bounds of an aggregate with
480       --  discrete choices whose index type is an enumeration, we build static
481       --  expressions not recognized by Compile_Time_Known_Value as such since
482       --  they have not yet been analyzed and resolved. All the expressions in
483       --  question are things like Index_Base_Name'Val (Const) which we can
484       --  easily recognize as being constant.
485
486       ---------
487       -- Add --
488       ---------
489
490       function Add (Val : Int; To : Node_Id) return Node_Id is
491          Expr_Pos : Node_Id;
492          Expr     : Node_Id;
493          To_Pos   : Node_Id;
494          U_To     : Uint;
495          U_Val    : constant Uint := UI_From_Int (Val);
496
497       begin
498          --  Note: do not try to optimize the case of Val = 0, because
499          --  we need to build a new node with the proper Sloc value anyway.
500
501          --  First test if we can do constant folding
502
503          if Local_Compile_Time_Known_Value (To) then
504             U_To := Local_Expr_Value (To) + Val;
505
506             --  Determine if our constant is outside the range of the index.
507             --  If so return an Empty node. This empty node will be caught
508             --  by Empty_Range below.
509
510             if Compile_Time_Known_Value (Index_Base_L)
511               and then U_To < Expr_Value (Index_Base_L)
512             then
513                return Empty;
514
515             elsif Compile_Time_Known_Value (Index_Base_H)
516               and then U_To > Expr_Value (Index_Base_H)
517             then
518                return Empty;
519             end if;
520
521             Expr_Pos := Make_Integer_Literal (Loc, U_To);
522             Set_Is_Static_Expression (Expr_Pos);
523
524             if not Is_Enumeration_Type (Index_Base) then
525                Expr := Expr_Pos;
526
527             --  If we are dealing with enumeration return
528             --     Index_Base'Val (Expr_Pos)
529
530             else
531                Expr :=
532                  Make_Attribute_Reference
533                    (Loc,
534                     Prefix         => Index_Base_Name,
535                     Attribute_Name => Name_Val,
536                     Expressions    => New_List (Expr_Pos));
537             end if;
538
539             return Expr;
540          end if;
541
542          --  If we are here no constant folding possible
543
544          if not Is_Enumeration_Type (Index_Base) then
545             Expr :=
546               Make_Op_Add (Loc,
547                            Left_Opnd  => Duplicate_Subexpr (To),
548                            Right_Opnd => Make_Integer_Literal (Loc, U_Val));
549
550          --  If we are dealing with enumeration return
551          --    Index_Base'Val (Index_Base'Pos (To) + Val)
552
553          else
554             To_Pos :=
555               Make_Attribute_Reference
556                 (Loc,
557                  Prefix         => Index_Base_Name,
558                  Attribute_Name => Name_Pos,
559                  Expressions    => New_List (Duplicate_Subexpr (To)));
560
561             Expr_Pos :=
562               Make_Op_Add (Loc,
563                            Left_Opnd  => To_Pos,
564                            Right_Opnd => Make_Integer_Literal (Loc, U_Val));
565
566             Expr :=
567               Make_Attribute_Reference
568                 (Loc,
569                  Prefix         => Index_Base_Name,
570                  Attribute_Name => Name_Val,
571                  Expressions    => New_List (Expr_Pos));
572          end if;
573
574          return Expr;
575       end Add;
576
577       -----------------
578       -- Empty_Range --
579       -----------------
580
581       function Empty_Range (L, H : Node_Id) return Boolean is
582          Is_Empty : Boolean := False;
583          Low      : Node_Id;
584          High     : Node_Id;
585
586       begin
587          --  First check if L or H were already detected as overflowing the
588          --  index base range type by function Add above. If this is so Add
589          --  returns the empty node.
590
591          if No (L) or else No (H) then
592             return True;
593          end if;
594
595          for J in 1 .. 3 loop
596             case J is
597
598                --  L > H    range is empty
599
600                when 1 =>
601                   Low  := L;
602                   High := H;
603
604                --  B_L > H  range must be empty
605
606                when 2 =>
607                   Low  := Index_Base_L;
608                   High := H;
609
610                --  L > B_H  range must be empty
611
612                when 3 =>
613                   Low  := L;
614                   High := Index_Base_H;
615             end case;
616
617             if Local_Compile_Time_Known_Value (Low)
618               and then Local_Compile_Time_Known_Value (High)
619             then
620                Is_Empty :=
621                  UI_Gt (Local_Expr_Value (Low), Local_Expr_Value (High));
622             end if;
623
624             exit when Is_Empty;
625          end loop;
626
627          return Is_Empty;
628       end Empty_Range;
629
630       -----------
631       -- Equal --
632       -----------
633
634       function Equal (L, H : Node_Id) return Boolean is
635       begin
636          if L = H then
637             return True;
638
639          elsif Local_Compile_Time_Known_Value (L)
640            and then Local_Compile_Time_Known_Value (H)
641          then
642             return UI_Eq (Local_Expr_Value (L), Local_Expr_Value (H));
643          end if;
644
645          return False;
646       end Equal;
647
648       ----------------
649       -- Gen_Assign --
650       ----------------
651
652       function Gen_Assign (Ind : Node_Id; Expr : Node_Id) return List_Id is
653          L : constant List_Id := New_List;
654          F : Entity_Id;
655          A : Node_Id;
656
657          New_Indices  : List_Id;
658          Indexed_Comp : Node_Id;
659          Expr_Q       : Node_Id;
660          Comp_Type    : Entity_Id := Empty;
661
662          function Add_Loop_Actions (Lis : List_Id) return List_Id;
663          --  Collect insert_actions generated in the construction of a
664          --  loop, and prepend them to the sequence of assignments to
665          --  complete the eventual body of the loop.
666
667          ----------------------
668          -- Add_Loop_Actions --
669          ----------------------
670
671          function Add_Loop_Actions (Lis : List_Id) return List_Id is
672             Res : List_Id;
673
674          begin
675             --  Ada 2005 (AI-287): Do nothing else in case of default
676             --  initialized component.
677
678             if not Present (Expr) then
679                return Lis;
680
681             elsif Nkind (Parent (Expr)) = N_Component_Association
682               and then Present (Loop_Actions (Parent (Expr)))
683             then
684                Append_List (Lis, Loop_Actions (Parent (Expr)));
685                Res := Loop_Actions (Parent (Expr));
686                Set_Loop_Actions (Parent (Expr), No_List);
687                return Res;
688
689             else
690                return Lis;
691             end if;
692          end Add_Loop_Actions;
693
694       --  Start of processing for Gen_Assign
695
696       begin
697          if No (Indices) then
698             New_Indices := New_List;
699          else
700             New_Indices := New_Copy_List_Tree (Indices);
701          end if;
702
703          Append_To (New_Indices, Ind);
704
705          if Present (Flist) then
706             F := New_Copy_Tree (Flist);
707
708          elsif Present (Etype (N)) and then Controlled_Type (Etype (N)) then
709             if Is_Entity_Name (Into)
710               and then Present (Scope (Entity (Into)))
711             then
712                F := Find_Final_List (Scope (Entity (Into)));
713             else
714                F := Find_Final_List (Current_Scope);
715             end if;
716          else
717             F := Empty;
718          end if;
719
720          if Present (Next_Index (Index)) then
721             return
722               Add_Loop_Actions (
723                 Build_Array_Aggr_Code
724                   (N           => Expr,
725                    Ctype       => Ctype,
726                    Index       => Next_Index (Index),
727                    Into        => Into,
728                    Scalar_Comp => Scalar_Comp,
729                    Indices     => New_Indices,
730                    Flist       => F));
731          end if;
732
733          --  If we get here then we are at a bottom-level (sub-)aggregate
734
735          Indexed_Comp :=
736            Checks_Off
737              (Make_Indexed_Component (Loc,
738                 Prefix      => New_Copy_Tree (Into),
739                 Expressions => New_Indices));
740
741          Set_Assignment_OK (Indexed_Comp);
742
743          --  Ada 2005 (AI-287): In case of default initialized component, Expr
744          --  is not present (and therefore we also initialize Expr_Q to empty).
745
746          if not Present (Expr) then
747             Expr_Q := Empty;
748          elsif Nkind (Expr) = N_Qualified_Expression then
749             Expr_Q := Expression (Expr);
750          else
751             Expr_Q := Expr;
752          end if;
753
754          if Present (Etype (N))
755            and then Etype (N) /= Any_Composite
756          then
757             Comp_Type := Component_Type (Etype (N));
758             pragma Assert (Comp_Type = Ctype); --  AI-287
759
760          elsif Present (Next (First (New_Indices))) then
761
762             --  Ada 2005 (AI-287): Do nothing in case of default initialized
763             --  component because we have received the component type in
764             --  the formal parameter Ctype.
765
766             --  ??? Some assert pragmas have been added to check if this new
767             --      formal can be used to replace this code in all cases.
768
769             if Present (Expr) then
770
771                --  This is a multidimensional array. Recover the component
772                --  type from the outermost aggregate, because subaggregates
773                --  do not have an assigned type.
774
775                declare
776                   P : Node_Id := Parent (Expr);
777
778                begin
779                   while Present (P) loop
780                      if Nkind (P) = N_Aggregate
781                        and then Present (Etype (P))
782                      then
783                         Comp_Type := Component_Type (Etype (P));
784                         exit;
785
786                      else
787                         P := Parent (P);
788                      end if;
789                   end loop;
790
791                   pragma Assert (Comp_Type = Ctype); --  AI-287
792                end;
793             end if;
794          end if;
795
796          --  Ada 2005 (AI-287): We only analyze the expression in case of non-
797          --  default initialized components (otherwise Expr_Q is not present).
798
799          if Present (Expr_Q)
800            and then (Nkind (Expr_Q) = N_Aggregate
801                      or else Nkind (Expr_Q) = N_Extension_Aggregate)
802          then
803             --  At this stage the Expression may not have been
804             --  analyzed yet because the array aggregate code has not
805             --  been updated to use the Expansion_Delayed flag and
806             --  avoid analysis altogether to solve the same problem
807             --  (see Resolve_Aggr_Expr). So let us do the analysis of
808             --  non-array aggregates now in order to get the value of
809             --  Expansion_Delayed flag for the inner aggregate ???
810
811             if Present (Comp_Type) and then not Is_Array_Type (Comp_Type) then
812                Analyze_And_Resolve (Expr_Q, Comp_Type);
813             end if;
814
815             if Is_Delayed_Aggregate (Expr_Q) then
816                return
817                  Add_Loop_Actions (
818                    Late_Expansion (Expr_Q, Etype (Expr_Q), Indexed_Comp, F));
819             end if;
820          end if;
821
822          --  Ada 2005 (AI-287): In case of default initialized component, call
823          --  the initialization subprogram associated with the component type.
824
825          if not Present (Expr) then
826
827             if Present (Base_Init_Proc (Etype (Ctype)))
828               or else Has_Task (Base_Type (Ctype))
829             then
830                Append_List_To (L,
831                  Build_Initialization_Call (Loc,
832                    Id_Ref            => Indexed_Comp,
833                    Typ               => Ctype,
834                    With_Default_Init => True));
835             end if;
836
837          else
838             --  Now generate the assignment with no associated controlled
839             --  actions since the target of the assignment may not have
840             --  been initialized, it is not possible to Finalize it as
841             --  expected by normal controlled assignment. The rest of the
842             --  controlled actions are done manually with the proper
843             --  finalization list coming from the context.
844
845             A :=
846               Make_OK_Assignment_Statement (Loc,
847                 Name       => Indexed_Comp,
848                 Expression => New_Copy_Tree (Expr));
849
850             if Present (Comp_Type) and then Controlled_Type (Comp_Type) then
851                Set_No_Ctrl_Actions (A);
852             end if;
853
854             Append_To (L, A);
855
856             --  Adjust the tag if tagged (because of possible view
857             --  conversions), unless compiling for the Java VM
858             --  where tags are implicit.
859
860             if Present (Comp_Type)
861               and then Is_Tagged_Type (Comp_Type)
862               and then not Java_VM
863             then
864                A :=
865                  Make_OK_Assignment_Statement (Loc,
866                    Name =>
867                      Make_Selected_Component (Loc,
868                        Prefix =>  New_Copy_Tree (Indexed_Comp),
869                        Selector_Name =>
870                          New_Reference_To (Tag_Component (Comp_Type), Loc)),
871
872                    Expression =>
873                      Unchecked_Convert_To (RTE (RE_Tag),
874                        New_Reference_To (
875                          Access_Disp_Table (Comp_Type), Loc)));
876
877                Append_To (L, A);
878             end if;
879
880             --  Adjust and Attach the component to the proper final list
881             --  which can be the controller of the outer record object or
882             --  the final list associated with the scope
883
884             if Present (Comp_Type)  and then Controlled_Type (Comp_Type) then
885                Append_List_To (L,
886                  Make_Adjust_Call (
887                    Ref         => New_Copy_Tree (Indexed_Comp),
888                    Typ         => Comp_Type,
889                    Flist_Ref   => F,
890                    With_Attach => Make_Integer_Literal (Loc, 1)));
891             end if;
892          end if;
893
894          return Add_Loop_Actions (L);
895       end Gen_Assign;
896
897       --------------
898       -- Gen_Loop --
899       --------------
900
901       function Gen_Loop (L, H : Node_Id; Expr : Node_Id) return List_Id is
902          L_J : Node_Id;
903
904          L_Range : Node_Id;
905          --  Index_Base'(L) .. Index_Base'(H)
906
907          L_Iteration_Scheme : Node_Id;
908          --  L_J in Index_Base'(L) .. Index_Base'(H)
909
910          L_Body : List_Id;
911          --  The statements to execute in the loop
912
913          S : constant List_Id := New_List;
914          --  List of statements
915
916          Tcopy : Node_Id;
917          --  Copy of expression tree, used for checking purposes
918
919       begin
920          --  If loop bounds define an empty range return the null statement
921
922          if Empty_Range (L, H) then
923             Append_To (S, Make_Null_Statement (Loc));
924
925             --  Ada 2005 (AI-287): Nothing else need to be done in case of
926             --  default initialized component.
927
928             if not Present (Expr) then
929                null;
930
931             else
932                --  The expression must be type-checked even though no component
933                --  of the aggregate will have this value. This is done only for
934                --  actual components of the array, not for subaggregates. Do
935                --  the check on a copy, because the expression may be shared
936                --  among several choices, some of which might be non-null.
937
938                if Present (Etype (N))
939                  and then Is_Array_Type (Etype (N))
940                  and then No (Next_Index (Index))
941                then
942                   Expander_Mode_Save_And_Set (False);
943                   Tcopy := New_Copy_Tree (Expr);
944                   Set_Parent (Tcopy, N);
945                   Analyze_And_Resolve (Tcopy, Component_Type (Etype (N)));
946                   Expander_Mode_Restore;
947                end if;
948             end if;
949
950             return S;
951
952          --  If loop bounds are the same then generate an assignment
953
954          elsif Equal (L, H) then
955             return Gen_Assign (New_Copy_Tree (L), Expr);
956
957          --  If H - L <= 2 then generate a sequence of assignments
958          --  when we are processing the bottom most aggregate and it contains
959          --  scalar components.
960
961          elsif No (Next_Index (Index))
962            and then Scalar_Comp
963            and then Local_Compile_Time_Known_Value (L)
964            and then Local_Compile_Time_Known_Value (H)
965            and then Local_Expr_Value (H) - Local_Expr_Value (L) <= 2
966          then
967
968             Append_List_To (S, Gen_Assign (New_Copy_Tree (L), Expr));
969             Append_List_To (S, Gen_Assign (Add (1, To => L), Expr));
970
971             if Local_Expr_Value (H) - Local_Expr_Value (L) = 2 then
972                Append_List_To (S, Gen_Assign (Add (2, To => L), Expr));
973             end if;
974
975             return S;
976          end if;
977
978          --  Otherwise construct the loop, starting with the loop index L_J
979
980          L_J := Make_Defining_Identifier (Loc, New_Internal_Name ('J'));
981
982          --  Construct "L .. H"
983
984          L_Range :=
985            Make_Range
986              (Loc,
987               Low_Bound  => Make_Qualified_Expression
988                               (Loc,
989                                Subtype_Mark => Index_Base_Name,
990                                Expression   => L),
991               High_Bound => Make_Qualified_Expression
992                               (Loc,
993                                Subtype_Mark => Index_Base_Name,
994                                Expression => H));
995
996          --  Construct "for L_J in Index_Base range L .. H"
997
998          L_Iteration_Scheme :=
999            Make_Iteration_Scheme
1000              (Loc,
1001               Loop_Parameter_Specification =>
1002                 Make_Loop_Parameter_Specification
1003                   (Loc,
1004                    Defining_Identifier         => L_J,
1005                    Discrete_Subtype_Definition => L_Range));
1006
1007          --  Construct the statements to execute in the loop body
1008
1009          L_Body := Gen_Assign (New_Reference_To (L_J, Loc), Expr);
1010
1011          --  Construct the final loop
1012
1013          Append_To (S, Make_Implicit_Loop_Statement
1014                          (Node             => N,
1015                           Identifier       => Empty,
1016                           Iteration_Scheme => L_Iteration_Scheme,
1017                           Statements       => L_Body));
1018
1019          return S;
1020       end Gen_Loop;
1021
1022       ---------------
1023       -- Gen_While --
1024       ---------------
1025
1026       --  The code built is
1027
1028       --     W_J : Index_Base := L;
1029       --     while W_J < H loop
1030       --        W_J := Index_Base'Succ (W);
1031       --        L_Body;
1032       --     end loop;
1033
1034       function Gen_While (L, H : Node_Id; Expr : Node_Id) return List_Id is
1035          W_J : Node_Id;
1036
1037          W_Decl : Node_Id;
1038          --  W_J : Base_Type := L;
1039
1040          W_Iteration_Scheme : Node_Id;
1041          --  while W_J < H
1042
1043          W_Index_Succ : Node_Id;
1044          --  Index_Base'Succ (J)
1045
1046          W_Increment : Node_Id;
1047          --  W_J := Index_Base'Succ (W)
1048
1049          W_Body : constant List_Id := New_List;
1050          --  The statements to execute in the loop
1051
1052          S : constant List_Id := New_List;
1053          --  list of statement
1054
1055       begin
1056          --  If loop bounds define an empty range or are equal return null
1057
1058          if Empty_Range (L, H) or else Equal (L, H) then
1059             Append_To (S, Make_Null_Statement (Loc));
1060             return S;
1061          end if;
1062
1063          --  Build the decl of W_J
1064
1065          W_J    := Make_Defining_Identifier (Loc, New_Internal_Name ('J'));
1066          W_Decl :=
1067            Make_Object_Declaration
1068              (Loc,
1069               Defining_Identifier => W_J,
1070               Object_Definition   => Index_Base_Name,
1071               Expression          => L);
1072
1073          --  Theoretically we should do a New_Copy_Tree (L) here, but we know
1074          --  that in this particular case L is a fresh Expr generated by
1075          --  Add which we are the only ones to use.
1076
1077          Append_To (S, W_Decl);
1078
1079          --  Construct " while W_J < H"
1080
1081          W_Iteration_Scheme :=
1082            Make_Iteration_Scheme
1083              (Loc,
1084               Condition => Make_Op_Lt
1085                              (Loc,
1086                               Left_Opnd  => New_Reference_To (W_J, Loc),
1087                               Right_Opnd => New_Copy_Tree (H)));
1088
1089          --  Construct the statements to execute in the loop body
1090
1091          W_Index_Succ :=
1092            Make_Attribute_Reference
1093              (Loc,
1094               Prefix         => Index_Base_Name,
1095               Attribute_Name => Name_Succ,
1096               Expressions    => New_List (New_Reference_To (W_J, Loc)));
1097
1098          W_Increment  :=
1099            Make_OK_Assignment_Statement
1100              (Loc,
1101               Name       => New_Reference_To (W_J, Loc),
1102               Expression => W_Index_Succ);
1103
1104          Append_To (W_Body, W_Increment);
1105          Append_List_To (W_Body,
1106            Gen_Assign (New_Reference_To (W_J, Loc), Expr));
1107
1108          --  Construct the final loop
1109
1110          Append_To (S, Make_Implicit_Loop_Statement
1111                          (Node             => N,
1112                           Identifier       => Empty,
1113                           Iteration_Scheme => W_Iteration_Scheme,
1114                           Statements       => W_Body));
1115
1116          return S;
1117       end Gen_While;
1118
1119       ---------------------
1120       -- Index_Base_Name --
1121       ---------------------
1122
1123       function Index_Base_Name return Node_Id is
1124       begin
1125          return New_Reference_To (Index_Base, Sloc (N));
1126       end Index_Base_Name;
1127
1128       ------------------------------------
1129       -- Local_Compile_Time_Known_Value --
1130       ------------------------------------
1131
1132       function Local_Compile_Time_Known_Value (E : Node_Id) return Boolean is
1133       begin
1134          return Compile_Time_Known_Value (E)
1135            or else
1136              (Nkind (E) = N_Attribute_Reference
1137                and then Attribute_Name (E) = Name_Val
1138                and then Compile_Time_Known_Value (First (Expressions (E))));
1139       end Local_Compile_Time_Known_Value;
1140
1141       ----------------------
1142       -- Local_Expr_Value --
1143       ----------------------
1144
1145       function Local_Expr_Value (E : Node_Id) return Uint is
1146       begin
1147          if Compile_Time_Known_Value (E) then
1148             return Expr_Value (E);
1149          else
1150             return Expr_Value (First (Expressions (E)));
1151          end if;
1152       end Local_Expr_Value;
1153
1154       --  Build_Array_Aggr_Code Variables
1155
1156       Assoc  : Node_Id;
1157       Choice : Node_Id;
1158       Expr   : Node_Id;
1159       Typ    : Entity_Id;
1160
1161       Others_Expr         : Node_Id := Empty;
1162       Others_Mbox_Present : Boolean := False;
1163
1164       Aggr_L : constant Node_Id := Low_Bound (Aggregate_Bounds (N));
1165       Aggr_H : constant Node_Id := High_Bound (Aggregate_Bounds (N));
1166       --  The aggregate bounds of this specific sub-aggregate. Note that if
1167       --  the code generated by Build_Array_Aggr_Code is executed then these
1168       --  bounds are OK. Otherwise a Constraint_Error would have been raised.
1169
1170       Aggr_Low  : constant Node_Id := Duplicate_Subexpr_No_Checks (Aggr_L);
1171       Aggr_High : constant Node_Id := Duplicate_Subexpr_No_Checks (Aggr_H);
1172       --  After Duplicate_Subexpr these are side-effect free
1173
1174       Low        : Node_Id;
1175       High       : Node_Id;
1176
1177       Nb_Choices : Nat := 0;
1178       Table      : Case_Table_Type (1 .. Number_Of_Choices (N));
1179       --  Used to sort all the different choice values
1180
1181       Nb_Elements : Int;
1182       --  Number of elements in the positional aggregate
1183
1184       New_Code : constant List_Id := New_List;
1185
1186    --  Start of processing for Build_Array_Aggr_Code
1187
1188    begin
1189       --  First before we start, a special case. if we have a bit packed
1190       --  array represented as a modular type, then clear the value to
1191       --  zero first, to ensure that unused bits are properly cleared.
1192
1193       Typ := Etype (N);
1194
1195       if Present (Typ)
1196         and then Is_Bit_Packed_Array (Typ)
1197         and then Is_Modular_Integer_Type (Packed_Array_Type (Typ))
1198       then
1199          Append_To (New_Code,
1200            Make_Assignment_Statement (Loc,
1201              Name => New_Copy_Tree (Into),
1202              Expression =>
1203                Unchecked_Convert_To (Typ,
1204                  Make_Integer_Literal (Loc, Uint_0))));
1205       end if;
1206
1207       --  We can skip this
1208       --  STEP 1: Process component associations
1209       --  For those associations that may generate a loop, initialize
1210       --  Loop_Actions to collect inserted actions that may be crated.
1211
1212       if No (Expressions (N)) then
1213
1214          --  STEP 1 (a): Sort the discrete choices
1215
1216          Assoc := First (Component_Associations (N));
1217          while Present (Assoc) loop
1218             Choice := First (Choices (Assoc));
1219             while Present (Choice) loop
1220                if Nkind (Choice) = N_Others_Choice then
1221                   Set_Loop_Actions (Assoc, New_List);
1222
1223                   if Box_Present (Assoc) then
1224                      Others_Mbox_Present := True;
1225                   else
1226                      Others_Expr := Expression (Assoc);
1227                   end if;
1228                   exit;
1229                end if;
1230
1231                Get_Index_Bounds (Choice, Low, High);
1232
1233                if Low /= High then
1234                   Set_Loop_Actions (Assoc, New_List);
1235                end if;
1236
1237                Nb_Choices := Nb_Choices + 1;
1238                if Box_Present (Assoc) then
1239                   Table (Nb_Choices) := (Choice_Lo   => Low,
1240                                          Choice_Hi   => High,
1241                                          Choice_Node => Empty);
1242                else
1243                   Table (Nb_Choices) := (Choice_Lo   => Low,
1244                                          Choice_Hi   => High,
1245                                          Choice_Node => Expression (Assoc));
1246                end if;
1247                Next (Choice);
1248             end loop;
1249
1250             Next (Assoc);
1251          end loop;
1252
1253          --  If there is more than one set of choices these must be static
1254          --  and we can therefore sort them. Remember that Nb_Choices does not
1255          --  account for an others choice.
1256
1257          if Nb_Choices > 1 then
1258             Sort_Case_Table (Table);
1259          end if;
1260
1261          --  STEP 1 (b):  take care of the whole set of discrete choices.
1262
1263          for J in 1 .. Nb_Choices loop
1264             Low  := Table (J).Choice_Lo;
1265             High := Table (J).Choice_Hi;
1266             Expr := Table (J).Choice_Node;
1267             Append_List (Gen_Loop (Low, High, Expr), To => New_Code);
1268          end loop;
1269
1270          --  STEP 1 (c): generate the remaining loops to cover others choice
1271          --  We don't need to generate loops over empty gaps, but if there is
1272          --  a single empty range we must analyze the expression for semantics
1273
1274          if Present (Others_Expr) or else Others_Mbox_Present then
1275             declare
1276                First : Boolean := True;
1277
1278             begin
1279                for J in 0 .. Nb_Choices loop
1280                   if J = 0 then
1281                      Low := Aggr_Low;
1282                   else
1283                      Low := Add (1, To => Table (J).Choice_Hi);
1284                   end if;
1285
1286                   if J = Nb_Choices then
1287                      High := Aggr_High;
1288                   else
1289                      High := Add (-1, To => Table (J + 1).Choice_Lo);
1290                   end if;
1291
1292                   --  If this is an expansion within an init proc, make
1293                   --  sure that discriminant references are replaced by
1294                   --  the corresponding discriminal.
1295
1296                   if Inside_Init_Proc then
1297                      if Is_Entity_Name (Low)
1298                        and then Ekind (Entity (Low)) = E_Discriminant
1299                      then
1300                         Set_Entity (Low, Discriminal (Entity (Low)));
1301                      end if;
1302
1303                      if Is_Entity_Name (High)
1304                        and then Ekind (Entity (High)) = E_Discriminant
1305                      then
1306                         Set_Entity (High, Discriminal (Entity (High)));
1307                      end if;
1308                   end if;
1309
1310                   if First
1311                     or else not Empty_Range (Low, High)
1312                   then
1313                      First := False;
1314                      Append_List
1315                        (Gen_Loop (Low, High, Others_Expr), To => New_Code);
1316                   end if;
1317                end loop;
1318             end;
1319          end if;
1320
1321       --  STEP 2: Process positional components
1322
1323       else
1324          --  STEP 2 (a): Generate the assignments for each positional element
1325          --  Note that here we have to use Aggr_L rather than Aggr_Low because
1326          --  Aggr_L is analyzed and Add wants an analyzed expression.
1327
1328          Expr        := First (Expressions (N));
1329          Nb_Elements := -1;
1330
1331          while Present (Expr) loop
1332             Nb_Elements := Nb_Elements + 1;
1333             Append_List (Gen_Assign (Add (Nb_Elements, To => Aggr_L), Expr),
1334                          To => New_Code);
1335             Next (Expr);
1336          end loop;
1337
1338          --  STEP 2 (b): Generate final loop if an others choice is present
1339          --  Here Nb_Elements gives the offset of the last positional element.
1340
1341          if Present (Component_Associations (N)) then
1342             Assoc := Last (Component_Associations (N));
1343
1344             --  Ada 2005 (AI-287)
1345
1346             if Box_Present (Assoc) then
1347                Append_List (Gen_While (Add (Nb_Elements, To => Aggr_L),
1348                                        Aggr_High,
1349                                        Empty),
1350                             To => New_Code);
1351             else
1352                Expr  := Expression (Assoc);
1353
1354                Append_List (Gen_While (Add (Nb_Elements, To => Aggr_L),
1355                                        Aggr_High,
1356                                        Expr), --  AI-287
1357                             To => New_Code);
1358             end if;
1359          end if;
1360       end if;
1361
1362       return New_Code;
1363    end Build_Array_Aggr_Code;
1364
1365    ----------------------------
1366    -- Build_Record_Aggr_Code --
1367    ----------------------------
1368
1369    function Build_Record_Aggr_Code
1370      (N                             : Node_Id;
1371       Typ                           : Entity_Id;
1372       Target                        : Node_Id;
1373       Flist                         : Node_Id   := Empty;
1374       Obj                           : Entity_Id := Empty;
1375       Is_Limited_Ancestor_Expansion : Boolean   := False) return List_Id
1376    is
1377       Loc     : constant Source_Ptr := Sloc (N);
1378       L       : constant List_Id    := New_List;
1379       Start_L : constant List_Id    := New_List;
1380       N_Typ   : constant Entity_Id  := Etype (N);
1381
1382       Comp      : Node_Id;
1383       Instr     : Node_Id;
1384       Ref       : Node_Id;
1385       F         : Node_Id;
1386       Comp_Type : Entity_Id;
1387       Selector  : Entity_Id;
1388       Comp_Expr : Node_Id;
1389       Expr_Q    : Node_Id;
1390
1391       Internal_Final_List : Node_Id;
1392
1393       --  If this is an internal aggregate, the External_Final_List is an
1394       --  expression for the controller record of the enclosing type.
1395       --  If the current aggregate has several controlled components, this
1396       --  expression will appear in several calls to attach to the finali-
1397       --  zation list, and it must not be shared.
1398
1399       External_Final_List      : Node_Id;
1400       Ancestor_Is_Expression   : Boolean := False;
1401       Ancestor_Is_Subtype_Mark : Boolean := False;
1402
1403       Init_Typ : Entity_Id := Empty;
1404       Attach   : Node_Id;
1405
1406       function Get_Constraint_Association (T : Entity_Id) return Node_Id;
1407       --  Returns the first discriminant association in the constraint
1408       --  associated with T, if any, otherwise returns Empty.
1409
1410       function Ancestor_Discriminant_Value (Disc : Entity_Id) return Node_Id;
1411       --  Returns the value that the given discriminant of an ancestor
1412       --  type should receive (in the absence of a conflict with the
1413       --  value provided by an ancestor part of an extension aggregate).
1414
1415       procedure Check_Ancestor_Discriminants (Anc_Typ : Entity_Id);
1416       --  Check that each of the discriminant values defined by the
1417       --  ancestor part of an extension aggregate match the corresponding
1418       --  values provided by either an association of the aggregate or
1419       --  by the constraint imposed by a parent type (RM95-4.3.2(8)).
1420
1421       function Init_Controller
1422         (Target  : Node_Id;
1423          Typ     : Entity_Id;
1424          F       : Node_Id;
1425          Attach  : Node_Id;
1426          Init_Pr : Boolean) return List_Id;
1427       --  returns the list of statements necessary to initialize the internal
1428       --  controller of the (possible) ancestor typ into target and attach
1429       --  it to finalization list F. Init_Pr conditions the call to the
1430       --  init proc since it may already be done due to ancestor initialization
1431
1432       ---------------------------------
1433       -- Ancestor_Discriminant_Value --
1434       ---------------------------------
1435
1436       function Ancestor_Discriminant_Value (Disc : Entity_Id) return Node_Id is
1437          Assoc        : Node_Id;
1438          Assoc_Elmt   : Elmt_Id;
1439          Aggr_Comp    : Entity_Id;
1440          Corresp_Disc : Entity_Id;
1441          Current_Typ  : Entity_Id := Base_Type (Typ);
1442          Parent_Typ   : Entity_Id;
1443          Parent_Disc  : Entity_Id;
1444          Save_Assoc   : Node_Id := Empty;
1445
1446       begin
1447          --  First check any discriminant associations to see if
1448          --  any of them provide a value for the discriminant.
1449
1450          if Present (Discriminant_Specifications (Parent (Current_Typ))) then
1451             Assoc := First (Component_Associations (N));
1452             while Present (Assoc) loop
1453                Aggr_Comp := Entity (First (Choices (Assoc)));
1454
1455                if Ekind (Aggr_Comp) = E_Discriminant then
1456                   Save_Assoc := Expression (Assoc);
1457
1458                   Corresp_Disc := Corresponding_Discriminant (Aggr_Comp);
1459                   while Present (Corresp_Disc) loop
1460                      --  If found a corresponding discriminant then return
1461                      --  the value given in the aggregate. (Note: this is
1462                      --  not correct in the presence of side effects. ???)
1463
1464                      if Disc = Corresp_Disc then
1465                         return Duplicate_Subexpr (Expression (Assoc));
1466                      end if;
1467
1468                      Corresp_Disc :=
1469                        Corresponding_Discriminant (Corresp_Disc);
1470                   end loop;
1471                end if;
1472
1473                Next (Assoc);
1474             end loop;
1475          end if;
1476
1477          --  No match found in aggregate, so chain up parent types to find
1478          --  a constraint that defines the value of the discriminant.
1479
1480          Parent_Typ := Etype (Current_Typ);
1481          while Current_Typ /= Parent_Typ loop
1482             if Has_Discriminants (Parent_Typ) then
1483                Parent_Disc := First_Discriminant (Parent_Typ);
1484
1485                --  We either get the association from the subtype indication
1486                --  of the type definition itself, or from the discriminant
1487                --  constraint associated with the type entity (which is
1488                --  preferable, but it's not always present ???)
1489
1490                if Is_Empty_Elmt_List (
1491                  Discriminant_Constraint (Current_Typ))
1492                then
1493                   Assoc := Get_Constraint_Association (Current_Typ);
1494                   Assoc_Elmt := No_Elmt;
1495                else
1496                   Assoc_Elmt :=
1497                     First_Elmt (Discriminant_Constraint (Current_Typ));
1498                   Assoc := Node (Assoc_Elmt);
1499                end if;
1500
1501                --  Traverse the discriminants of the parent type looking
1502                --  for one that corresponds.
1503
1504                while Present (Parent_Disc) and then Present (Assoc) loop
1505                   Corresp_Disc := Parent_Disc;
1506                   while Present (Corresp_Disc)
1507                     and then Disc /= Corresp_Disc
1508                   loop
1509                      Corresp_Disc :=
1510                        Corresponding_Discriminant (Corresp_Disc);
1511                   end loop;
1512
1513                   if Disc = Corresp_Disc then
1514                      if Nkind (Assoc) = N_Discriminant_Association then
1515                         Assoc := Expression (Assoc);
1516                      end if;
1517
1518                      --  If the located association directly denotes
1519                      --  a discriminant, then use the value of a saved
1520                      --  association of the aggregate. This is a kludge
1521                      --  to handle certain cases involving multiple
1522                      --  discriminants mapped to a single discriminant
1523                      --  of a descendant. It's not clear how to locate the
1524                      --  appropriate discriminant value for such cases. ???
1525
1526                      if Is_Entity_Name (Assoc)
1527                        and then Ekind (Entity (Assoc)) = E_Discriminant
1528                      then
1529                         Assoc := Save_Assoc;
1530                      end if;
1531
1532                      return Duplicate_Subexpr (Assoc);
1533                   end if;
1534
1535                   Next_Discriminant (Parent_Disc);
1536
1537                   if No (Assoc_Elmt) then
1538                      Next (Assoc);
1539                   else
1540                      Next_Elmt (Assoc_Elmt);
1541                      if Present (Assoc_Elmt) then
1542                         Assoc := Node (Assoc_Elmt);
1543                      else
1544                         Assoc := Empty;
1545                      end if;
1546                   end if;
1547                end loop;
1548             end if;
1549
1550             Current_Typ := Parent_Typ;
1551             Parent_Typ := Etype (Current_Typ);
1552          end loop;
1553
1554          --  In some cases there's no ancestor value to locate (such as
1555          --  when an ancestor part given by an expression defines the
1556          --  discriminant value).
1557
1558          return Empty;
1559       end Ancestor_Discriminant_Value;
1560
1561       ----------------------------------
1562       -- Check_Ancestor_Discriminants --
1563       ----------------------------------
1564
1565       procedure Check_Ancestor_Discriminants (Anc_Typ : Entity_Id) is
1566          Discr      : Entity_Id := First_Discriminant (Base_Type (Anc_Typ));
1567          Disc_Value : Node_Id;
1568          Cond       : Node_Id;
1569
1570       begin
1571          while Present (Discr) loop
1572             Disc_Value := Ancestor_Discriminant_Value (Discr);
1573
1574             if Present (Disc_Value) then
1575                Cond := Make_Op_Ne (Loc,
1576                  Left_Opnd =>
1577                    Make_Selected_Component (Loc,
1578                      Prefix        => New_Copy_Tree (Target),
1579                      Selector_Name => New_Occurrence_Of (Discr, Loc)),
1580                  Right_Opnd => Disc_Value);
1581
1582                Append_To (L,
1583                  Make_Raise_Constraint_Error (Loc,
1584                    Condition => Cond,
1585                    Reason    => CE_Discriminant_Check_Failed));
1586             end if;
1587
1588             Next_Discriminant (Discr);
1589          end loop;
1590       end Check_Ancestor_Discriminants;
1591
1592       --------------------------------
1593       -- Get_Constraint_Association --
1594       --------------------------------
1595
1596       function Get_Constraint_Association (T : Entity_Id) return Node_Id is
1597          Typ_Def : constant Node_Id := Type_Definition (Parent (T));
1598          Indic   : constant Node_Id := Subtype_Indication (Typ_Def);
1599
1600       begin
1601          --  ??? Also need to cover case of a type mark denoting a subtype
1602          --  with constraint.
1603
1604          if Nkind (Indic) = N_Subtype_Indication
1605            and then Present (Constraint (Indic))
1606          then
1607             return First (Constraints (Constraint (Indic)));
1608          end if;
1609
1610          return Empty;
1611       end Get_Constraint_Association;
1612
1613       ---------------------
1614       -- Init_controller --
1615       ---------------------
1616
1617       function Init_Controller
1618         (Target  : Node_Id;
1619          Typ     : Entity_Id;
1620          F       : Node_Id;
1621          Attach  : Node_Id;
1622          Init_Pr : Boolean) return List_Id
1623       is
1624          L   : constant List_Id := New_List;
1625          Ref : Node_Id;
1626
1627       begin
1628          --  Generate:
1629          --     init-proc (target._controller);
1630          --     initialize (target._controller);
1631          --     Attach_to_Final_List (target._controller, F);
1632
1633          Ref :=
1634            Make_Selected_Component (Loc,
1635              Prefix        => Convert_To (Typ, New_Copy_Tree (Target)),
1636              Selector_Name => Make_Identifier (Loc, Name_uController));
1637          Set_Assignment_OK (Ref);
1638
1639          --  Ada 2005 (AI-287): Give support to default initialization of
1640          --  limited types and components.
1641
1642          if (Nkind (Target) = N_Identifier
1643               and then Present (Etype (Target))
1644               and then Is_Limited_Type (Etype (Target)))
1645            or else
1646             (Nkind (Target) = N_Selected_Component
1647               and then Present (Etype (Selector_Name (Target)))
1648               and then Is_Limited_Type (Etype (Selector_Name (Target))))
1649            or else
1650             (Nkind (Target) = N_Unchecked_Type_Conversion
1651               and then Present (Etype (Target))
1652               and then Is_Limited_Type (Etype (Target)))
1653            or else
1654             (Nkind (Target) = N_Unchecked_Expression
1655               and then Nkind (Expression (Target)) = N_Indexed_Component
1656               and then Present (Etype (Prefix (Expression (Target))))
1657               and then Is_Limited_Type (Etype (Prefix (Expression (Target)))))
1658          then
1659             if Init_Pr then
1660                Append_List_To (L,
1661                  Build_Initialization_Call (Loc,
1662                    Id_Ref       => Ref,
1663                    Typ          => RTE (RE_Limited_Record_Controller),
1664                    In_Init_Proc => Within_Init_Proc));
1665             end if;
1666
1667             Append_To (L,
1668               Make_Procedure_Call_Statement (Loc,
1669                 Name =>
1670                   New_Reference_To
1671                          (Find_Prim_Op (RTE (RE_Limited_Record_Controller),
1672                     Name_Initialize), Loc),
1673                 Parameter_Associations => New_List (New_Copy_Tree (Ref))));
1674
1675          else
1676             if Init_Pr then
1677                Append_List_To (L,
1678                  Build_Initialization_Call (Loc,
1679                    Id_Ref       => Ref,
1680                    Typ          => RTE (RE_Record_Controller),
1681                    In_Init_Proc => Within_Init_Proc));
1682             end if;
1683
1684             Append_To (L,
1685               Make_Procedure_Call_Statement (Loc,
1686                 Name =>
1687                   New_Reference_To (Find_Prim_Op (RTE (RE_Record_Controller),
1688                     Name_Initialize), Loc),
1689                 Parameter_Associations => New_List (New_Copy_Tree (Ref))));
1690
1691          end if;
1692
1693          Append_To (L,
1694            Make_Attach_Call (
1695              Obj_Ref     => New_Copy_Tree (Ref),
1696              Flist_Ref   => F,
1697              With_Attach => Attach));
1698          return L;
1699       end Init_Controller;
1700
1701    --  Start of processing for Build_Record_Aggr_Code
1702
1703    begin
1704       --  Deal with the ancestor part of extension aggregates
1705       --  or with the discriminants of the root type
1706
1707       if Nkind (N) = N_Extension_Aggregate then
1708          declare
1709             A : constant Node_Id := Ancestor_Part (N);
1710
1711          begin
1712             --  If the ancestor part is a subtype mark "T", we generate
1713
1714             --     init-proc (T(tmp));  if T is constrained and
1715             --     init-proc (S(tmp));  where S applies an appropriate
1716             --                           constraint if T is unconstrained
1717
1718             if Is_Entity_Name (A) and then Is_Type (Entity (A)) then
1719                Ancestor_Is_Subtype_Mark := True;
1720
1721                if Is_Constrained (Entity (A)) then
1722                   Init_Typ := Entity (A);
1723
1724                --  For an ancestor part given by an unconstrained type
1725                --  mark, create a subtype constrained by appropriate
1726                --  corresponding discriminant values coming from either
1727                --  associations of the aggregate or a constraint on
1728                --  a parent type. The subtype will be used to generate
1729                --  the correct default value for the ancestor part.
1730
1731                elsif Has_Discriminants (Entity (A)) then
1732                   declare
1733                      Anc_Typ    : constant Entity_Id := Entity (A);
1734                      Anc_Constr : constant List_Id   := New_List;
1735                      Discrim    : Entity_Id;
1736                      Disc_Value : Node_Id;
1737                      New_Indic  : Node_Id;
1738                      Subt_Decl  : Node_Id;
1739
1740                   begin
1741                      Discrim := First_Discriminant (Anc_Typ);
1742                      while Present (Discrim) loop
1743                         Disc_Value := Ancestor_Discriminant_Value (Discrim);
1744                         Append_To (Anc_Constr, Disc_Value);
1745                         Next_Discriminant (Discrim);
1746                      end loop;
1747
1748                      New_Indic :=
1749                        Make_Subtype_Indication (Loc,
1750                          Subtype_Mark => New_Occurrence_Of (Anc_Typ, Loc),
1751                          Constraint   =>
1752                            Make_Index_Or_Discriminant_Constraint (Loc,
1753                              Constraints => Anc_Constr));
1754
1755                      Init_Typ := Create_Itype (Ekind (Anc_Typ), N);
1756
1757                      Subt_Decl :=
1758                        Make_Subtype_Declaration (Loc,
1759                          Defining_Identifier => Init_Typ,
1760                          Subtype_Indication  => New_Indic);
1761
1762                      --  Itypes must be analyzed with checks off
1763                      --  Declaration must have a parent for proper
1764                      --  handling of subsidiary actions.
1765
1766                      Set_Parent (Subt_Decl, N);
1767                      Analyze (Subt_Decl, Suppress => All_Checks);
1768                   end;
1769                end if;
1770
1771                Ref := Convert_To (Init_Typ, New_Copy_Tree (Target));
1772                Set_Assignment_OK (Ref);
1773
1774                if Has_Default_Init_Comps (N)
1775                  or else Has_Task (Base_Type (Init_Typ))
1776                then
1777                   Append_List_To (Start_L,
1778                     Build_Initialization_Call (Loc,
1779                       Id_Ref       => Ref,
1780                       Typ          => Init_Typ,
1781                       In_Init_Proc => Within_Init_Proc,
1782                       With_Default_Init => True));
1783                else
1784                   Append_List_To (Start_L,
1785                     Build_Initialization_Call (Loc,
1786                       Id_Ref       => Ref,
1787                       Typ          => Init_Typ,
1788                       In_Init_Proc => Within_Init_Proc));
1789                end if;
1790
1791                if Is_Constrained (Entity (A))
1792                  and then Has_Discriminants (Entity (A))
1793                then
1794                   Check_Ancestor_Discriminants (Entity (A));
1795                end if;
1796
1797             --  Ada 2005 (AI-287): If the ancestor part is a limited type,
1798             --  a recursive call expands the ancestor.
1799
1800             elsif Is_Limited_Type (Etype (A)) then
1801                Ancestor_Is_Expression := True;
1802
1803                Append_List_To (Start_L,
1804                   Build_Record_Aggr_Code (
1805                     N                             => Expression (A),
1806                     Typ                           => Etype (Expression (A)),
1807                     Target                        => Target,
1808                     Flist                         => Flist,
1809                     Obj                           => Obj,
1810                     Is_Limited_Ancestor_Expansion => True));
1811
1812             --  If the ancestor part is an expression "E", we generate
1813             --     T(tmp) := E;
1814
1815             else
1816                Ancestor_Is_Expression := True;
1817                Init_Typ := Etype (A);
1818
1819                --  Assign the tag before doing the assignment to make sure
1820                --  that the dispatching call in the subsequent deep_adjust
1821                --  works properly (unless Java_VM, where tags are implicit).
1822
1823                if not Java_VM then
1824                   Instr :=
1825                     Make_OK_Assignment_Statement (Loc,
1826                       Name =>
1827                         Make_Selected_Component (Loc,
1828                           Prefix => New_Copy_Tree (Target),
1829                           Selector_Name => New_Reference_To (
1830                             Tag_Component (Base_Type (Typ)), Loc)),
1831
1832                       Expression =>
1833                         Unchecked_Convert_To (RTE (RE_Tag),
1834                           New_Reference_To (
1835                             Access_Disp_Table (Base_Type (Typ)), Loc)));
1836
1837                   Set_Assignment_OK (Name (Instr));
1838                   Append_To (L, Instr);
1839                end if;
1840
1841                --  If the ancestor part is an aggregate, force its full
1842                --  expansion, which was delayed.
1843
1844                if Nkind (A) = N_Qualified_Expression
1845                  and then (Nkind (Expression (A)) = N_Aggregate
1846                              or else
1847                            Nkind (Expression (A)) = N_Extension_Aggregate)
1848                then
1849                   Set_Analyzed (A, False);
1850                   Set_Analyzed (Expression (A), False);
1851                end if;
1852
1853                Ref := Convert_To (Init_Typ, New_Copy_Tree (Target));
1854                Set_Assignment_OK (Ref);
1855                Append_To (L,
1856                  Make_Unsuppress_Block (Loc,
1857                    Name_Discriminant_Check,
1858                    New_List (
1859                      Make_OK_Assignment_Statement (Loc,
1860                        Name       => Ref,
1861                        Expression => A))));
1862
1863                if Has_Discriminants (Init_Typ) then
1864                   Check_Ancestor_Discriminants (Init_Typ);
1865                end if;
1866             end if;
1867          end;
1868
1869       --  Normal case (not an extension aggregate)
1870
1871       else
1872          --  Generate the discriminant expressions, component by component.
1873          --  If the base type is an unchecked union, the discriminants are
1874          --  unknown to the back-end and absent from a value of the type, so
1875          --  assignments for them are not emitted.
1876
1877          if Has_Discriminants (Typ)
1878            and then not Is_Unchecked_Union (Base_Type (Typ))
1879          then
1880             --  ??? The discriminants of the object not inherited in the type
1881             --  of the object should be initialized here
1882
1883             null;
1884
1885             --  Generate discriminant init values
1886
1887             declare
1888                Discriminant : Entity_Id;
1889                Discriminant_Value : Node_Id;
1890
1891             begin
1892                Discriminant := First_Stored_Discriminant (Typ);
1893
1894                while Present (Discriminant) loop
1895
1896                   Comp_Expr :=
1897                     Make_Selected_Component (Loc,
1898                       Prefix        => New_Copy_Tree (Target),
1899                       Selector_Name => New_Occurrence_Of (Discriminant, Loc));
1900
1901                   Discriminant_Value :=
1902                     Get_Discriminant_Value (
1903                       Discriminant,
1904                       N_Typ,
1905                       Discriminant_Constraint (N_Typ));
1906
1907                   Instr :=
1908                     Make_OK_Assignment_Statement (Loc,
1909                       Name       => Comp_Expr,
1910                       Expression => New_Copy_Tree (Discriminant_Value));
1911
1912                   Set_No_Ctrl_Actions (Instr);
1913                   Append_To (L, Instr);
1914
1915                   Next_Stored_Discriminant (Discriminant);
1916                end loop;
1917             end;
1918          end if;
1919       end if;
1920
1921       --  Generate the assignments, component by component
1922
1923       --    tmp.comp1 := Expr1_From_Aggr;
1924       --    tmp.comp2 := Expr2_From_Aggr;
1925       --    ....
1926
1927       Comp := First (Component_Associations (N));
1928       while Present (Comp) loop
1929          Selector := Entity (First (Choices (Comp)));
1930
1931          --  Ada 2005 (AI-287): Default initialization of a limited component
1932
1933          if Box_Present (Comp)
1934             and then Is_Limited_Type (Etype (Selector))
1935          then
1936             --  Ada 2005 (AI-287): If the component type has tasks then
1937             --  generate the activation chain and master entities (except
1938             --  in case of an allocator because in that case these entities
1939             --  are generated by Build_Task_Allocate_Block_With_Init_Stmts).
1940
1941             declare
1942                Ctype            : constant Entity_Id := Etype (Selector);
1943                Inside_Allocator : Boolean   := False;
1944                P                : Node_Id   := Parent (N);
1945
1946             begin
1947                if Is_Task_Type (Ctype) or else Has_Task (Ctype) then
1948                   while Present (P) loop
1949                      if Nkind (P) = N_Allocator then
1950                         Inside_Allocator := True;
1951                         exit;
1952                      end if;
1953
1954                      P := Parent (P);
1955                   end loop;
1956
1957                   if not Inside_Init_Proc and not Inside_Allocator then
1958                      Build_Activation_Chain_Entity (N);
1959
1960                      if not Has_Master_Entity (Current_Scope) then
1961                         Build_Master_Entity (Etype (N));
1962                      end if;
1963                   end if;
1964                end if;
1965             end;
1966
1967             Append_List_To (L,
1968               Build_Initialization_Call (Loc,
1969                 Id_Ref => Make_Selected_Component (Loc,
1970                             Prefix => New_Copy_Tree (Target),
1971                             Selector_Name => New_Occurrence_Of (Selector,
1972                                                                    Loc)),
1973                 Typ    => Etype (Selector),
1974                 With_Default_Init => True));
1975
1976             goto Next_Comp;
1977          end if;
1978
1979          --  ???
1980
1981          if Ekind (Selector) /= E_Discriminant
1982            or else Nkind (N) = N_Extension_Aggregate
1983          then
1984             Comp_Type := Etype (Selector);
1985             Comp_Expr :=
1986               Make_Selected_Component (Loc,
1987                 Prefix        => New_Copy_Tree (Target),
1988                 Selector_Name => New_Occurrence_Of (Selector, Loc));
1989
1990             if Nkind (Expression (Comp)) = N_Qualified_Expression then
1991                Expr_Q := Expression (Expression (Comp));
1992             else
1993                Expr_Q := Expression (Comp);
1994             end if;
1995
1996             --  The controller is the one of the parent type defining
1997             --  the component (in case of inherited components).
1998
1999             if Controlled_Type (Comp_Type) then
2000                Internal_Final_List :=
2001                  Make_Selected_Component (Loc,
2002                    Prefix => Convert_To (
2003                      Scope (Original_Record_Component (Selector)),
2004                      New_Copy_Tree (Target)),
2005                    Selector_Name =>
2006                      Make_Identifier (Loc, Name_uController));
2007
2008                Internal_Final_List :=
2009                  Make_Selected_Component (Loc,
2010                    Prefix => Internal_Final_List,
2011                    Selector_Name => Make_Identifier (Loc, Name_F));
2012
2013                --  The internal final list can be part of a constant object
2014
2015                Set_Assignment_OK (Internal_Final_List);
2016
2017             else
2018                Internal_Final_List := Empty;
2019             end if;
2020
2021             --  ???
2022
2023             if Is_Delayed_Aggregate (Expr_Q) then
2024                Append_List_To (L,
2025                  Late_Expansion (Expr_Q, Comp_Type, Comp_Expr,
2026                    Internal_Final_List));
2027
2028             else
2029                Instr :=
2030                  Make_OK_Assignment_Statement (Loc,
2031                    Name       => Comp_Expr,
2032                    Expression => Expression (Comp));
2033
2034                Set_No_Ctrl_Actions (Instr);
2035                Append_To (L, Instr);
2036
2037                --  Adjust the tag if tagged (because of possible view
2038                --  conversions), unless compiling for the Java VM
2039                --  where tags are implicit.
2040
2041                --    tmp.comp._tag := comp_typ'tag;
2042
2043                if Is_Tagged_Type (Comp_Type) and then not Java_VM then
2044                   Instr :=
2045                     Make_OK_Assignment_Statement (Loc,
2046                       Name =>
2047                         Make_Selected_Component (Loc,
2048                           Prefix =>  New_Copy_Tree (Comp_Expr),
2049                           Selector_Name =>
2050                             New_Reference_To (Tag_Component (Comp_Type), Loc)),
2051
2052                       Expression =>
2053                         Unchecked_Convert_To (RTE (RE_Tag),
2054                           New_Reference_To (
2055                             Access_Disp_Table (Comp_Type), Loc)));
2056
2057                   Append_To (L, Instr);
2058                end if;
2059
2060                --  Adjust and Attach the component to the proper controller
2061                --     Adjust (tmp.comp);
2062                --     Attach_To_Final_List (tmp.comp,
2063                --       comp_typ (tmp)._record_controller.f)
2064
2065                if Controlled_Type (Comp_Type) then
2066                   Append_List_To (L,
2067                     Make_Adjust_Call (
2068                       Ref         => New_Copy_Tree (Comp_Expr),
2069                       Typ         => Comp_Type,
2070                       Flist_Ref   => Internal_Final_List,
2071                       With_Attach => Make_Integer_Literal (Loc, 1)));
2072                end if;
2073             end if;
2074
2075          --  ???
2076
2077          elsif Ekind (Selector) = E_Discriminant
2078            and then Nkind (N) /= N_Extension_Aggregate
2079            and then Nkind (Parent (N)) = N_Component_Association
2080            and then Is_Constrained (Typ)
2081          then
2082             --  We must check that the discriminant value imposed by the
2083             --  context is the same as the value given in the subaggregate,
2084             --  because after the expansion into assignments there is no
2085             --  record on which to perform a regular discriminant check.
2086
2087             declare
2088                D_Val : Elmt_Id;
2089                Disc  : Entity_Id;
2090
2091             begin
2092                D_Val := First_Elmt (Discriminant_Constraint (Typ));
2093                Disc  := First_Discriminant (Typ);
2094
2095                while Chars (Disc) /= Chars (Selector) loop
2096                   Next_Discriminant (Disc);
2097                   Next_Elmt (D_Val);
2098                end loop;
2099
2100                pragma Assert (Present (D_Val));
2101
2102                Append_To (L,
2103                Make_Raise_Constraint_Error (Loc,
2104                  Condition =>
2105                    Make_Op_Ne (Loc,
2106                      Left_Opnd => New_Copy_Tree (Node (D_Val)),
2107                      Right_Opnd => Expression (Comp)),
2108                  Reason => CE_Discriminant_Check_Failed));
2109             end;
2110          end if;
2111
2112          <<Next_Comp>>
2113
2114          Next (Comp);
2115       end loop;
2116
2117       --  If the type is tagged, the tag needs to be initialized (unless
2118       --  compiling for the Java VM where tags are implicit). It is done
2119       --  late in the initialization process because in some cases, we call
2120       --  the init proc of an ancestor which will not leave out the right tag
2121
2122       if Ancestor_Is_Expression then
2123          null;
2124
2125       elsif Is_Tagged_Type (Typ) and then not Java_VM then
2126          Instr :=
2127            Make_OK_Assignment_Statement (Loc,
2128              Name =>
2129                Make_Selected_Component (Loc,
2130                   Prefix => New_Copy_Tree (Target),
2131                  Selector_Name =>
2132                    New_Reference_To (Tag_Component (Base_Type (Typ)), Loc)),
2133
2134              Expression =>
2135                Unchecked_Convert_To (RTE (RE_Tag),
2136                  New_Reference_To (Access_Disp_Table (Base_Type (Typ)), Loc)));
2137
2138          Append_To (L, Instr);
2139       end if;
2140
2141       --  Now deal with the various controlled type data structure
2142       --  initializations
2143
2144       if Present (Obj)
2145         and then Finalize_Storage_Only (Typ)
2146         and then (Is_Library_Level_Entity (Obj)
2147         or else Entity (Constant_Value (RTE (RE_Garbage_Collected)))
2148                   = Standard_True)
2149       then
2150          Attach := Make_Integer_Literal (Loc, 0);
2151
2152       elsif Nkind (Parent (N)) = N_Qualified_Expression
2153         and then Nkind (Parent (Parent (N))) = N_Allocator
2154       then
2155          Attach := Make_Integer_Literal (Loc, 2);
2156
2157       else
2158          Attach := Make_Integer_Literal (Loc, 1);
2159       end if;
2160
2161       --  Determine the external finalization list. It is either the
2162       --  finalization list of the outer-scope or the one coming from
2163       --  an outer aggregate.  When the target is not a temporary, the
2164       --  proper scope is the scope of the target rather than the
2165       --  potentially transient current scope.
2166
2167       if Controlled_Type (Typ) then
2168          if Present (Flist) then
2169             External_Final_List := New_Copy_Tree (Flist);
2170
2171          elsif Is_Entity_Name (Target)
2172            and then Present (Scope (Entity (Target)))
2173          then
2174             External_Final_List := Find_Final_List (Scope (Entity (Target)));
2175
2176          else
2177             External_Final_List := Find_Final_List (Current_Scope);
2178          end if;
2179
2180       else
2181          External_Final_List := Empty;
2182       end if;
2183
2184       --  Initialize and attach the outer object in the is_controlled case
2185
2186       if Is_Controlled (Typ) then
2187          if Ancestor_Is_Subtype_Mark then
2188             Ref := Convert_To (Init_Typ, New_Copy_Tree (Target));
2189             Set_Assignment_OK (Ref);
2190             Append_To (L,
2191               Make_Procedure_Call_Statement (Loc,
2192                 Name => New_Reference_To (
2193                   Find_Prim_Op (Init_Typ, Name_Initialize), Loc),
2194                 Parameter_Associations => New_List (New_Copy_Tree (Ref))));
2195          end if;
2196
2197          if not Has_Controlled_Component (Typ) then
2198             Ref := New_Copy_Tree (Target);
2199             Set_Assignment_OK (Ref);
2200             Append_To (Start_L,
2201               Make_Attach_Call (
2202                 Obj_Ref     => Ref,
2203                 Flist_Ref   => New_Copy_Tree (External_Final_List),
2204                 With_Attach => Attach));
2205          end if;
2206       end if;
2207
2208       --  In the Has_Controlled component case, all the intermediate
2209       --  controllers must be initialized
2210
2211       if Has_Controlled_Component (Typ)
2212         and not Is_Limited_Ancestor_Expansion
2213       then
2214          declare
2215             Inner_Typ : Entity_Id;
2216             Outer_Typ : Entity_Id;
2217             At_Root   : Boolean;
2218
2219          begin
2220
2221             Outer_Typ := Base_Type (Typ);
2222
2223             --  Find outer type with a controller
2224
2225             while Outer_Typ /= Init_Typ
2226               and then not Has_New_Controlled_Component (Outer_Typ)
2227             loop
2228                Outer_Typ := Etype (Outer_Typ);
2229             end loop;
2230
2231             --  Attach it to the outer record controller to the
2232             --  external final list
2233
2234             if Outer_Typ = Init_Typ then
2235                Append_List_To (Start_L,
2236                  Init_Controller (
2237                    Target  => Target,
2238                    Typ     => Outer_Typ,
2239                    F       => External_Final_List,
2240                    Attach  => Attach,
2241                    Init_Pr => Ancestor_Is_Expression));
2242
2243                At_Root   := True;
2244                Inner_Typ := Init_Typ;
2245
2246             else
2247                Append_List_To (Start_L,
2248                  Init_Controller (
2249                    Target  => Target,
2250                    Typ     => Outer_Typ,
2251                    F       => External_Final_List,
2252                    Attach  => Attach,
2253                    Init_Pr => True));
2254
2255                Inner_Typ := Etype (Outer_Typ);
2256                At_Root   :=
2257                  not Is_Tagged_Type (Typ) or else Inner_Typ = Outer_Typ;
2258             end if;
2259
2260             --  The outer object has to be attached as well
2261
2262             if Is_Controlled (Typ) then
2263                Ref := New_Copy_Tree (Target);
2264                Set_Assignment_OK (Ref);
2265                Append_To (Start_L,
2266                   Make_Attach_Call (
2267                     Obj_Ref     => Ref,
2268                     Flist_Ref   => New_Copy_Tree (External_Final_List),
2269                     With_Attach => New_Copy_Tree (Attach)));
2270             end if;
2271
2272             --  Initialize the internal controllers for tagged types with
2273             --  more than one controller.
2274
2275             while not At_Root and then Inner_Typ /= Init_Typ loop
2276                if Has_New_Controlled_Component (Inner_Typ) then
2277                   F :=
2278                     Make_Selected_Component (Loc,
2279                       Prefix => Convert_To (Outer_Typ, New_Copy_Tree (Target)),
2280                       Selector_Name =>
2281                         Make_Identifier (Loc, Name_uController));
2282                   F :=
2283                     Make_Selected_Component (Loc,
2284                       Prefix => F,
2285                       Selector_Name => Make_Identifier (Loc, Name_F));
2286
2287                   Append_List_To (Start_L,
2288                     Init_Controller (
2289                       Target  => Target,
2290                       Typ     => Inner_Typ,
2291                       F       => F,
2292                       Attach  => Make_Integer_Literal (Loc, 1),
2293                       Init_Pr => True));
2294                   Outer_Typ := Inner_Typ;
2295                end if;
2296
2297                --  Stop at the root
2298
2299                At_Root := Inner_Typ = Etype (Inner_Typ);
2300                Inner_Typ := Etype (Inner_Typ);
2301             end loop;
2302
2303             --  If not done yet attach the controller of the ancestor part
2304
2305             if Outer_Typ /= Init_Typ
2306               and then Inner_Typ = Init_Typ
2307               and then Has_Controlled_Component (Init_Typ)
2308             then
2309                F :=
2310                   Make_Selected_Component (Loc,
2311                     Prefix => Convert_To (Outer_Typ, New_Copy_Tree (Target)),
2312                     Selector_Name => Make_Identifier (Loc, Name_uController));
2313                F :=
2314                   Make_Selected_Component (Loc,
2315                     Prefix => F,
2316                     Selector_Name => Make_Identifier (Loc, Name_F));
2317
2318                Attach := Make_Integer_Literal (Loc, 1);
2319                Append_List_To (Start_L,
2320                  Init_Controller (
2321                    Target  => Target,
2322                    Typ     => Init_Typ,
2323                    F       => F,
2324                    Attach  => Attach,
2325                    Init_Pr => Ancestor_Is_Expression));
2326             end if;
2327          end;
2328       end if;
2329
2330       Append_List_To (Start_L, L);
2331       return Start_L;
2332    end Build_Record_Aggr_Code;
2333
2334    -------------------------------
2335    -- Convert_Aggr_In_Allocator --
2336    -------------------------------
2337
2338    procedure Convert_Aggr_In_Allocator (Decl, Aggr : Node_Id) is
2339       Loc  : constant Source_Ptr := Sloc (Aggr);
2340       Typ  : constant Entity_Id  := Etype (Aggr);
2341       Temp : constant Entity_Id  := Defining_Identifier (Decl);
2342
2343       Occ  : constant Node_Id :=
2344                Unchecked_Convert_To (Typ,
2345                  Make_Explicit_Dereference (Loc,
2346                    New_Reference_To (Temp, Loc)));
2347
2348       Access_Type : constant Entity_Id := Etype (Temp);
2349
2350    begin
2351       if Has_Default_Init_Comps (Aggr) then
2352          declare
2353             L          : constant List_Id := New_List;
2354             Init_Stmts : List_Id;
2355
2356          begin
2357             Init_Stmts := Late_Expansion (Aggr, Typ, Occ,
2358                             Find_Final_List (Access_Type),
2359                             Associated_Final_Chain (Base_Type (Access_Type)));
2360
2361             Build_Task_Allocate_Block_With_Init_Stmts (L, Aggr, Init_Stmts);
2362             Insert_Actions_After (Decl, L);
2363          end;
2364
2365       else
2366          Insert_Actions_After (Decl,
2367            Late_Expansion (Aggr, Typ, Occ,
2368              Find_Final_List (Access_Type),
2369              Associated_Final_Chain (Base_Type (Access_Type))));
2370       end if;
2371    end Convert_Aggr_In_Allocator;
2372
2373    --------------------------------
2374    -- Convert_Aggr_In_Assignment --
2375    --------------------------------
2376
2377    procedure Convert_Aggr_In_Assignment (N : Node_Id) is
2378       Aggr : Node_Id             := Expression (N);
2379       Typ  : constant Entity_Id  := Etype (Aggr);
2380       Occ  : constant Node_Id    := New_Copy_Tree (Name (N));
2381
2382    begin
2383       if Nkind (Aggr) = N_Qualified_Expression then
2384          Aggr := Expression (Aggr);
2385       end if;
2386
2387       Insert_Actions_After (N,
2388         Late_Expansion (Aggr, Typ, Occ,
2389           Find_Final_List (Typ, New_Copy_Tree (Occ))));
2390    end Convert_Aggr_In_Assignment;
2391
2392    ---------------------------------
2393    -- Convert_Aggr_In_Object_Decl --
2394    ---------------------------------
2395
2396    procedure Convert_Aggr_In_Object_Decl (N : Node_Id) is
2397       Obj  : constant Entity_Id  := Defining_Identifier (N);
2398       Aggr : Node_Id             := Expression (N);
2399       Loc  : constant Source_Ptr := Sloc (Aggr);
2400       Typ  : constant Entity_Id  := Etype (Aggr);
2401       Occ  : constant Node_Id    := New_Occurrence_Of (Obj, Loc);
2402
2403       function Discriminants_Ok return Boolean;
2404       --  If the object type is constrained, the discriminants in the
2405       --  aggregate must be checked against the discriminants of the subtype.
2406       --  This cannot be done using Apply_Discriminant_Checks because after
2407       --  expansion there is no aggregate left to check.
2408
2409       ----------------------
2410       -- Discriminants_Ok --
2411       ----------------------
2412
2413       function Discriminants_Ok return Boolean is
2414          Cond  : Node_Id := Empty;
2415          Check : Node_Id;
2416          D     : Entity_Id;
2417          Disc1 : Elmt_Id;
2418          Disc2 : Elmt_Id;
2419          Val1  : Node_Id;
2420          Val2  : Node_Id;
2421
2422       begin
2423          D := First_Discriminant (Typ);
2424          Disc1 := First_Elmt (Discriminant_Constraint (Typ));
2425          Disc2 := First_Elmt (Discriminant_Constraint (Etype (Obj)));
2426
2427          while Present (Disc1) and then Present (Disc2) loop
2428             Val1 := Node (Disc1);
2429             Val2 := Node (Disc2);
2430
2431             if not Is_OK_Static_Expression (Val1)
2432               or else not Is_OK_Static_Expression (Val2)
2433             then
2434                Check := Make_Op_Ne (Loc,
2435                  Left_Opnd  => Duplicate_Subexpr (Val1),
2436                  Right_Opnd => Duplicate_Subexpr (Val2));
2437
2438                if No (Cond) then
2439                   Cond := Check;
2440
2441                else
2442                   Cond := Make_Or_Else (Loc,
2443                     Left_Opnd => Cond,
2444                     Right_Opnd => Check);
2445                end if;
2446
2447             elsif Expr_Value (Val1) /= Expr_Value (Val2) then
2448                Apply_Compile_Time_Constraint_Error (Aggr,
2449                  Msg    => "incorrect value for discriminant&?",
2450                  Reason => CE_Discriminant_Check_Failed,
2451                  Ent    => D);
2452                return False;
2453             end if;
2454
2455             Next_Discriminant (D);
2456             Next_Elmt (Disc1);
2457             Next_Elmt (Disc2);
2458          end loop;
2459
2460          --  If any discriminant constraint is non-static, emit a check.
2461
2462          if Present (Cond) then
2463             Insert_Action (N,
2464               Make_Raise_Constraint_Error (Loc,
2465                 Condition => Cond,
2466                 Reason => CE_Discriminant_Check_Failed));
2467          end if;
2468
2469          return True;
2470       end Discriminants_Ok;
2471
2472    --  Start of processing for Convert_Aggr_In_Object_Decl
2473
2474    begin
2475       Set_Assignment_OK (Occ);
2476
2477       if Nkind (Aggr) = N_Qualified_Expression then
2478          Aggr := Expression (Aggr);
2479       end if;
2480
2481       if Has_Discriminants (Typ)
2482         and then Typ /= Etype (Obj)
2483         and then Is_Constrained (Etype (Obj))
2484         and then not Discriminants_Ok
2485       then
2486          return;
2487       end if;
2488
2489       Insert_Actions_After (N, Late_Expansion (Aggr, Typ, Occ, Obj => Obj));
2490       Set_No_Initialization (N);
2491       Initialize_Discriminants (N, Typ);
2492    end Convert_Aggr_In_Object_Decl;
2493
2494    ----------------------------
2495    -- Convert_To_Assignments --
2496    ----------------------------
2497
2498    procedure Convert_To_Assignments (N : Node_Id; Typ : Entity_Id) is
2499       Loc  : constant Source_Ptr := Sloc (N);
2500       Temp : Entity_Id;
2501
2502       Instr       : Node_Id;
2503       Target_Expr : Node_Id;
2504       Parent_Kind : Node_Kind;
2505       Unc_Decl    : Boolean := False;
2506       Parent_Node : Node_Id;
2507
2508    begin
2509       Parent_Node := Parent (N);
2510       Parent_Kind := Nkind (Parent_Node);
2511
2512       if Parent_Kind = N_Qualified_Expression then
2513
2514          --  Check if we are in a unconstrained declaration because in this
2515          --  case the current delayed expansion mechanism doesn't work when
2516          --  the declared object size depend on the initializing expr.
2517
2518          begin
2519             Parent_Node := Parent (Parent_Node);
2520             Parent_Kind := Nkind (Parent_Node);
2521
2522             if Parent_Kind = N_Object_Declaration then
2523                Unc_Decl :=
2524                  not Is_Entity_Name (Object_Definition (Parent_Node))
2525                    or else Has_Discriminants
2526                              (Entity (Object_Definition (Parent_Node)))
2527                    or else Is_Class_Wide_Type
2528                              (Entity (Object_Definition (Parent_Node)));
2529             end if;
2530          end;
2531       end if;
2532
2533       --  Just set the Delay flag in the following cases where the
2534       --  transformation will be done top down from above
2535
2536       --    - internal aggregate (transformed when expanding the parent)
2537       --    - allocators  (see Convert_Aggr_In_Allocator)
2538       --    - object decl (see Convert_Aggr_In_Object_Decl)
2539       --    - safe assignments (see Convert_Aggr_Assignments)
2540       --      so far only the assignments in the init procs are taken
2541       --      into account
2542
2543       if Parent_Kind = N_Aggregate
2544         or else Parent_Kind = N_Extension_Aggregate
2545         or else Parent_Kind = N_Component_Association
2546         or else Parent_Kind = N_Allocator
2547         or else (Parent_Kind = N_Object_Declaration and then not Unc_Decl)
2548         or else (Parent_Kind = N_Assignment_Statement
2549                   and then Inside_Init_Proc)
2550       then
2551          Set_Expansion_Delayed (N);
2552          return;
2553       end if;
2554
2555       if Requires_Transient_Scope (Typ) then
2556          Establish_Transient_Scope (N, Sec_Stack =>
2557               Is_Controlled (Typ) or else Has_Controlled_Component (Typ));
2558       end if;
2559
2560       --  Create the temporary
2561
2562       Temp := Make_Defining_Identifier (Loc, New_Internal_Name ('A'));
2563
2564       Instr :=
2565         Make_Object_Declaration (Loc,
2566           Defining_Identifier => Temp,
2567           Object_Definition => New_Occurrence_Of (Typ, Loc));
2568
2569       Set_No_Initialization (Instr);
2570       Insert_Action (N, Instr);
2571       Initialize_Discriminants (Instr, Typ);
2572       Target_Expr := New_Occurrence_Of (Temp, Loc);
2573
2574       Insert_Actions (N, Build_Record_Aggr_Code (N, Typ, Target_Expr));
2575       Rewrite (N, New_Occurrence_Of (Temp, Loc));
2576       Analyze_And_Resolve (N, Typ);
2577    end Convert_To_Assignments;
2578
2579    ---------------------------
2580    -- Convert_To_Positional --
2581    ---------------------------
2582
2583    procedure Convert_To_Positional
2584      (N                    : Node_Id;
2585       Max_Others_Replicate : Nat     := 5;
2586       Handle_Bit_Packed    : Boolean := False)
2587    is
2588       Typ : constant Entity_Id := Etype (N);
2589
2590       function Flatten
2591         (N   : Node_Id;
2592          Ix  : Node_Id;
2593          Ixb : Node_Id) return Boolean;
2594       --  Convert the aggregate into a purely positional form if possible.
2595
2596       function Is_Flat (N : Node_Id; Dims : Int) return Boolean;
2597       --  Non trivial for multidimensional aggregate.
2598
2599       -------------
2600       -- Flatten --
2601       -------------
2602
2603       function Flatten
2604         (N   : Node_Id;
2605          Ix  : Node_Id;
2606          Ixb : Node_Id) return Boolean
2607       is
2608          Loc : constant Source_Ptr := Sloc (N);
2609          Blo : constant Node_Id    := Type_Low_Bound (Etype (Ixb));
2610          Lo  : constant Node_Id    := Type_Low_Bound (Etype (Ix));
2611          Hi  : constant Node_Id    := Type_High_Bound (Etype (Ix));
2612          Lov : Uint;
2613          Hiv : Uint;
2614
2615          --  The following constant determines the maximum size of an
2616          --  aggregate produced by converting named to positional
2617          --  notation (e.g. from others clauses). This avoids running
2618          --  away with attempts to convert huge aggregates.
2619
2620          --  The normal limit is 5000, but we increase this limit to
2621          --  2**24 (about 16 million) if Restrictions (No_Elaboration_Code)
2622          --  or Restrictions (No_Implicit_Loops) is specified, since in
2623          --  either case, we are at risk of declaring the program illegal
2624          --  because of this limit.
2625
2626          Max_Aggr_Size : constant Nat :=
2627                            5000 + (2 ** 24 - 5000) *
2628                              Boolean'Pos
2629                                (Restriction_Active (No_Elaboration_Code)
2630                                   or else
2631                                 Restriction_Active (No_Implicit_Loops));
2632
2633       begin
2634          if Nkind (Original_Node (N)) = N_String_Literal then
2635             return True;
2636          end if;
2637
2638          --  Bounds need to be known at compile time
2639
2640          if not Compile_Time_Known_Value (Lo)
2641            or else not Compile_Time_Known_Value (Hi)
2642          then
2643             return False;
2644          end if;
2645
2646          --  Get bounds and check reasonable size (positive, not too large)
2647          --  Also only handle bounds starting at the base type low bound
2648          --  for now since the compiler isn't able to handle different low
2649          --  bounds yet. Case such as new String'(3..5 => ' ') will get
2650          --  the wrong bounds, though it seems that the aggregate should
2651          --  retain the bounds set on its Etype (see C64103E and CC1311B).
2652
2653          Lov := Expr_Value (Lo);
2654          Hiv := Expr_Value (Hi);
2655
2656          if Hiv < Lov
2657            or else (Hiv - Lov > Max_Aggr_Size)
2658            or else not Compile_Time_Known_Value (Blo)
2659            or else (Lov /= Expr_Value (Blo))
2660          then
2661             return False;
2662          end if;
2663
2664          --  Bounds must be in integer range (for array Vals below)
2665
2666          if not UI_Is_In_Int_Range (Lov)
2667              or else
2668             not UI_Is_In_Int_Range (Hiv)
2669          then
2670             return False;
2671          end if;
2672
2673          --  Determine if set of alternatives is suitable for conversion
2674          --  and build an array containing the values in sequence.
2675
2676          declare
2677             Vals : array (UI_To_Int (Lov) .. UI_To_Int (Hiv))
2678                      of Node_Id := (others => Empty);
2679             --  The values in the aggregate sorted appropriately
2680
2681             Vlist : List_Id;
2682             --  Same data as Vals in list form
2683
2684             Rep_Count : Nat;
2685             --  Used to validate Max_Others_Replicate limit
2686
2687             Elmt   : Node_Id;
2688             Num    : Int := UI_To_Int (Lov);
2689             Choice : Node_Id;
2690             Lo, Hi : Node_Id;
2691
2692          begin
2693             if Present (Expressions (N)) then
2694                Elmt := First (Expressions (N));
2695
2696                while Present (Elmt) loop
2697                   if Nkind (Elmt) = N_Aggregate
2698                     and then Present (Next_Index (Ix))
2699                     and then
2700                          not Flatten (Elmt, Next_Index (Ix), Next_Index (Ixb))
2701                   then
2702                      return False;
2703                   end if;
2704
2705                   Vals (Num) := Relocate_Node (Elmt);
2706                   Num := Num + 1;
2707
2708                   Next (Elmt);
2709                end loop;
2710             end if;
2711
2712             if No (Component_Associations (N)) then
2713                return True;
2714             end if;
2715
2716             Elmt := First (Component_Associations (N));
2717
2718             if Nkind (Expression (Elmt)) = N_Aggregate then
2719                if Present (Next_Index (Ix))
2720                  and then
2721                    not Flatten
2722                         (Expression (Elmt), Next_Index (Ix), Next_Index (Ixb))
2723                then
2724                   return False;
2725                end if;
2726             end if;
2727
2728             Component_Loop : while Present (Elmt) loop
2729                Choice := First (Choices (Elmt));
2730                Choice_Loop : while Present (Choice) loop
2731
2732                   --  If we have an others choice, fill in the missing elements
2733                   --  subject to the limit established by Max_Others_Replicate.
2734
2735                   if Nkind (Choice) = N_Others_Choice then
2736                      Rep_Count := 0;
2737
2738                      for J in Vals'Range loop
2739                         if No (Vals (J)) then
2740                            Vals (J) := New_Copy_Tree (Expression (Elmt));
2741                            Rep_Count := Rep_Count + 1;
2742
2743                            --  Check for maximum others replication. Note that
2744                            --  we skip this test if either of the restrictions
2745                            --  No_Elaboration_Code or No_Implicit_Loops is
2746                            --  active, or if this is a preelaborable unit.
2747
2748                            declare
2749                               P : constant Entity_Id :=
2750                                     Cunit_Entity (Current_Sem_Unit);
2751
2752                            begin
2753                               if Restriction_Active (No_Elaboration_Code)
2754                                 or else Restriction_Active (No_Implicit_Loops)
2755                                 or else Is_Preelaborated (P)
2756                                 or else (Ekind (P) = E_Package_Body
2757                                           and then
2758                                             Is_Preelaborated (Spec_Entity (P)))
2759                               then
2760                                  null;
2761
2762                               elsif Rep_Count > Max_Others_Replicate then
2763                                  return False;
2764                               end if;
2765                            end;
2766                         end if;
2767                      end loop;
2768
2769                      exit Component_Loop;
2770
2771                   --  Case of a subtype mark
2772
2773                   elsif Nkind (Choice) = N_Identifier
2774                     and then Is_Type (Entity (Choice))
2775                   then
2776                      Lo := Type_Low_Bound  (Etype (Choice));
2777                      Hi := Type_High_Bound (Etype (Choice));
2778
2779                   --  Case of subtype indication
2780
2781                   elsif Nkind (Choice) = N_Subtype_Indication then
2782                      Lo := Low_Bound  (Range_Expression (Constraint (Choice)));
2783                      Hi := High_Bound (Range_Expression (Constraint (Choice)));
2784
2785                   --  Case of a range
2786
2787                   elsif Nkind (Choice) = N_Range then
2788                      Lo := Low_Bound (Choice);
2789                      Hi := High_Bound (Choice);
2790
2791                   --  Normal subexpression case
2792
2793                   else pragma Assert (Nkind (Choice) in N_Subexpr);
2794                      if not Compile_Time_Known_Value (Choice) then
2795                         return False;
2796
2797                      else
2798                         Vals (UI_To_Int (Expr_Value (Choice))) :=
2799                           New_Copy_Tree (Expression (Elmt));
2800                         goto Continue;
2801                      end if;
2802                   end if;
2803
2804                   --  Range cases merge with Lo,Hi said
2805
2806                   if not Compile_Time_Known_Value (Lo)
2807                        or else
2808                      not Compile_Time_Known_Value (Hi)
2809                   then
2810                      return False;
2811                   else
2812                      for J in UI_To_Int (Expr_Value (Lo)) ..
2813                               UI_To_Int (Expr_Value (Hi))
2814                      loop
2815                         Vals (J) := New_Copy_Tree (Expression (Elmt));
2816                      end loop;
2817                   end if;
2818
2819                <<Continue>>
2820                   Next (Choice);
2821                end loop Choice_Loop;
2822
2823                Next (Elmt);
2824             end loop Component_Loop;
2825
2826             --  If we get here the conversion is possible
2827
2828             Vlist := New_List;
2829             for J in Vals'Range loop
2830                Append (Vals (J), Vlist);
2831             end loop;
2832
2833             Rewrite (N, Make_Aggregate (Loc, Expressions => Vlist));
2834             Set_Aggregate_Bounds (N, Aggregate_Bounds (Original_Node (N)));
2835             return True;
2836          end;
2837       end Flatten;
2838
2839       -------------
2840       -- Is_Flat --
2841       -------------
2842
2843       function Is_Flat (N : Node_Id; Dims : Int) return Boolean is
2844          Elmt : Node_Id;
2845
2846       begin
2847          if Dims = 0 then
2848             return True;
2849
2850          elsif Nkind (N) = N_Aggregate then
2851             if Present (Component_Associations (N)) then
2852                return False;
2853
2854             else
2855                Elmt := First (Expressions (N));
2856
2857                while Present (Elmt) loop
2858                   if not Is_Flat (Elmt, Dims - 1) then
2859                      return False;
2860                   end if;
2861
2862                   Next (Elmt);
2863                end loop;
2864
2865                return True;
2866             end if;
2867          else
2868             return True;
2869          end if;
2870       end Is_Flat;
2871
2872    --  Start of processing for Convert_To_Positional
2873
2874    begin
2875       --  Ada 2005 (AI-287): Do not convert in case of default initialized
2876       --  components because in this case will need to call the corresponding
2877       --  IP procedure.
2878
2879       if Has_Default_Init_Comps (N) then
2880          return;
2881       end if;
2882
2883       if Is_Flat (N, Number_Dimensions (Typ)) then
2884          return;
2885       end if;
2886
2887       if Is_Bit_Packed_Array (Typ)
2888         and then not Handle_Bit_Packed
2889       then
2890          return;
2891       end if;
2892
2893       --  Do not convert to positional if controlled components are
2894       --  involved since these require special processing
2895
2896       if Has_Controlled_Component (Typ) then
2897          return;
2898       end if;
2899
2900       if Flatten (N, First_Index (Typ), First_Index (Base_Type (Typ))) then
2901          Analyze_And_Resolve (N, Typ);
2902       end if;
2903    end Convert_To_Positional;
2904
2905    ----------------------------
2906    -- Expand_Array_Aggregate --
2907    ----------------------------
2908
2909    --  Array aggregate expansion proceeds as follows:
2910
2911    --  1. If requested we generate code to perform all the array aggregate
2912    --     bound checks, specifically
2913
2914    --         (a) Check that the index range defined by aggregate bounds is
2915    --             compatible with corresponding index subtype.
2916
2917    --         (b) If an others choice is present check that no aggregate
2918    --             index is outside the bounds of the index constraint.
2919
2920    --         (c) For multidimensional arrays make sure that all subaggregates
2921    --             corresponding to the same dimension have the same bounds.
2922
2923    --  2. Check for packed array aggregate which can be converted to a
2924    --     constant so that the aggregate disappeares completely.
2925
2926    --  3. Check case of nested aggregate. Generally nested aggregates are
2927    --     handled during the processing of the parent aggregate.
2928
2929    --  4. Check if the aggregate can be statically processed. If this is the
2930    --     case pass it as is to Gigi. Note that a necessary condition for
2931    --     static processing is that the aggregate be fully positional.
2932
2933    --  5. If in place aggregate expansion is possible (i.e. no need to create
2934    --     a temporary) then mark the aggregate as such and return. Otherwise
2935    --     create a new temporary and generate the appropriate initialization
2936    --     code.
2937
2938    procedure Expand_Array_Aggregate (N : Node_Id) is
2939       Loc : constant Source_Ptr := Sloc (N);
2940
2941       Typ  : constant Entity_Id := Etype (N);
2942       Ctyp : constant Entity_Id := Component_Type (Typ);
2943       --  Typ is the correct constrained array subtype of the aggregate
2944       --  Ctyp is the corresponding component type.
2945
2946       Aggr_Dimension : constant Pos := Number_Dimensions (Typ);
2947       --  Number of aggregate index dimensions.
2948
2949       Aggr_Low  : array (1 .. Aggr_Dimension) of Node_Id;
2950       Aggr_High : array (1 .. Aggr_Dimension) of Node_Id;
2951       --  Low and High bounds of the constraint for each aggregate index.
2952
2953       Aggr_Index_Typ : array (1 .. Aggr_Dimension) of Entity_Id;
2954       --  The type of each index.
2955
2956       Maybe_In_Place_OK : Boolean;
2957       --  If the type is neither controlled nor packed and the aggregate
2958       --  is the expression in an assignment, assignment in place may be
2959       --  possible, provided other conditions are met on the LHS.
2960
2961       Others_Present : array (1 .. Aggr_Dimension) of Boolean :=
2962                          (others => False);
2963       --  If Others_Present (J) is True, then there is an others choice
2964       --  in one of the sub-aggregates of N at dimension J.
2965
2966       procedure Build_Constrained_Type (Positional : Boolean);
2967       --  If the subtype is not static or unconstrained, build a constrained
2968       --  type using the computable sizes of the aggregate and its sub-
2969       --  aggregates.
2970
2971       procedure Check_Bounds (Aggr_Bounds : Node_Id; Index_Bounds : Node_Id);
2972       --  Checks that the bounds of Aggr_Bounds are within the bounds defined
2973       --  by Index_Bounds.
2974
2975       procedure Check_Same_Aggr_Bounds (Sub_Aggr : Node_Id; Dim : Pos);
2976       --  Checks that in a multi-dimensional array aggregate all subaggregates
2977       --  corresponding to the same dimension have the same bounds.
2978       --  Sub_Aggr is an array sub-aggregate. Dim is the dimension
2979       --  corresponding to the sub-aggregate.
2980
2981       procedure Compute_Others_Present (Sub_Aggr : Node_Id; Dim : Pos);
2982       --  Computes the values of array Others_Present. Sub_Aggr is the
2983       --  array sub-aggregate we start the computation from. Dim is the
2984       --  dimension corresponding to the sub-aggregate.
2985
2986       function Has_Address_Clause (D : Node_Id) return Boolean;
2987       --  If the aggregate is the expression in an object declaration, it
2988       --  cannot be expanded in place. This function does a lookahead in the
2989       --  current declarative part to find an address clause for the object
2990       --  being declared.
2991
2992       function In_Place_Assign_OK return Boolean;
2993       --  Simple predicate to determine whether an aggregate assignment can
2994       --  be done in place, because none of the new values can depend on the
2995       --  components of the target of the assignment.
2996
2997       function Must_Slide (N : Node_Id; Typ : Entity_Id) return Boolean;
2998       --  A static aggregate in an object declaration can in most cases be
2999       --  expanded in place. The one exception is when the aggregate is given
3000       --  with component associations that specify different bounds from those
3001       --  of the type definition in the object declaration. In this rather
3002       --  pathological case the aggregate must slide, and we must introduce
3003       --  an intermediate temporary to hold it.
3004
3005       procedure Others_Check (Sub_Aggr : Node_Id; Dim : Pos);
3006       --  Checks that if an others choice is present in any sub-aggregate no
3007       --  aggregate index is outside the bounds of the index constraint.
3008       --  Sub_Aggr is an array sub-aggregate. Dim is the dimension
3009       --  corresponding to the sub-aggregate.
3010
3011       ----------------------------
3012       -- Build_Constrained_Type --
3013       ----------------------------
3014
3015       procedure Build_Constrained_Type (Positional : Boolean) is
3016          Loc      : constant Source_Ptr := Sloc (N);
3017          Agg_Type : Entity_Id;
3018          Comp     : Node_Id;
3019          Decl     : Node_Id;
3020          Typ      : constant Entity_Id := Etype (N);
3021          Indices  : constant List_Id   := New_List;
3022          Num      : Int;
3023          Sub_Agg  : Node_Id;
3024
3025       begin
3026          Agg_Type :=
3027            Make_Defining_Identifier (
3028              Loc, New_Internal_Name ('A'));
3029
3030          --  If the aggregate is purely positional, all its subaggregates
3031          --  have the same size. We collect the dimensions from the first
3032          --  subaggregate at each level.
3033
3034          if Positional then
3035             Sub_Agg := N;
3036
3037             for D in 1 .. Number_Dimensions (Typ) loop
3038                Comp := First (Expressions (Sub_Agg));
3039
3040                Sub_Agg := Comp;
3041                Num := 0;
3042
3043                while Present (Comp) loop
3044                   Num := Num + 1;
3045                   Next (Comp);
3046                end loop;
3047
3048                Append (
3049                  Make_Range (Loc,
3050                    Low_Bound => Make_Integer_Literal (Loc, 1),
3051                    High_Bound =>
3052                           Make_Integer_Literal (Loc, Num)),
3053                  Indices);
3054             end loop;
3055
3056          else
3057             --  We know the aggregate type is unconstrained and the
3058             --  aggregate is not processable by the back end, therefore
3059             --  not necessarily positional. Retrieve the bounds of each
3060             --  dimension as computed earlier.
3061
3062             for D in 1 .. Number_Dimensions (Typ) loop
3063                Append (
3064                  Make_Range (Loc,
3065                     Low_Bound  => Aggr_Low  (D),
3066                     High_Bound => Aggr_High (D)),
3067                  Indices);
3068             end loop;
3069          end if;
3070
3071          Decl :=
3072            Make_Full_Type_Declaration (Loc,
3073                Defining_Identifier => Agg_Type,
3074                Type_Definition =>
3075                  Make_Constrained_Array_Definition (Loc,
3076                    Discrete_Subtype_Definitions => Indices,
3077                    Component_Definition =>
3078                      Make_Component_Definition (Loc,
3079                        Aliased_Present => False,
3080                        Subtype_Indication =>
3081                          New_Occurrence_Of (Component_Type (Typ), Loc))));
3082
3083          Insert_Action (N, Decl);
3084          Analyze (Decl);
3085          Set_Etype (N, Agg_Type);
3086          Set_Is_Itype (Agg_Type);
3087          Freeze_Itype (Agg_Type, N);
3088       end Build_Constrained_Type;
3089
3090       ------------------
3091       -- Check_Bounds --
3092       ------------------
3093
3094       procedure Check_Bounds (Aggr_Bounds : Node_Id; Index_Bounds : Node_Id) is
3095          Aggr_Lo : Node_Id;
3096          Aggr_Hi : Node_Id;
3097
3098          Ind_Lo  : Node_Id;
3099          Ind_Hi  : Node_Id;
3100
3101          Cond    : Node_Id := Empty;
3102
3103       begin
3104          Get_Index_Bounds (Aggr_Bounds, Aggr_Lo, Aggr_Hi);
3105          Get_Index_Bounds (Index_Bounds, Ind_Lo, Ind_Hi);
3106
3107          --  Generate the following test:
3108          --
3109          --    [constraint_error when
3110          --      Aggr_Lo <= Aggr_Hi and then
3111          --        (Aggr_Lo < Ind_Lo or else Aggr_Hi > Ind_Hi)]
3112          --
3113          --  As an optimization try to see if some tests are trivially vacuos
3114          --  because we are comparing an expression against itself.
3115
3116          if Aggr_Lo = Ind_Lo and then Aggr_Hi = Ind_Hi then
3117             Cond := Empty;
3118
3119          elsif Aggr_Hi = Ind_Hi then
3120             Cond :=
3121               Make_Op_Lt (Loc,
3122                 Left_Opnd  => Duplicate_Subexpr_Move_Checks (Aggr_Lo),
3123                 Right_Opnd => Duplicate_Subexpr_Move_Checks (Ind_Lo));
3124
3125          elsif Aggr_Lo = Ind_Lo then
3126             Cond :=
3127               Make_Op_Gt (Loc,
3128                 Left_Opnd  => Duplicate_Subexpr_Move_Checks (Aggr_Hi),
3129                 Right_Opnd => Duplicate_Subexpr_Move_Checks (Ind_Hi));
3130
3131          else
3132             Cond :=
3133               Make_Or_Else (Loc,
3134                 Left_Opnd =>
3135                   Make_Op_Lt (Loc,
3136                     Left_Opnd  => Duplicate_Subexpr_Move_Checks (Aggr_Lo),
3137                     Right_Opnd => Duplicate_Subexpr_Move_Checks (Ind_Lo)),
3138
3139                 Right_Opnd =>
3140                   Make_Op_Gt (Loc,
3141                     Left_Opnd  => Duplicate_Subexpr (Aggr_Hi),
3142                     Right_Opnd => Duplicate_Subexpr (Ind_Hi)));
3143          end if;
3144
3145          if Present (Cond) then
3146             Cond :=
3147               Make_And_Then (Loc,
3148                 Left_Opnd =>
3149                   Make_Op_Le (Loc,
3150                     Left_Opnd  => Duplicate_Subexpr_Move_Checks (Aggr_Lo),
3151                     Right_Opnd => Duplicate_Subexpr_Move_Checks (Aggr_Hi)),
3152
3153                 Right_Opnd => Cond);
3154
3155             Set_Analyzed (Left_Opnd  (Left_Opnd (Cond)), False);
3156             Set_Analyzed (Right_Opnd (Left_Opnd (Cond)), False);
3157             Insert_Action (N,
3158               Make_Raise_Constraint_Error (Loc,
3159                 Condition => Cond,
3160                 Reason    => CE_Length_Check_Failed));
3161          end if;
3162       end Check_Bounds;
3163
3164       ----------------------------
3165       -- Check_Same_Aggr_Bounds --
3166       ----------------------------
3167
3168       procedure Check_Same_Aggr_Bounds (Sub_Aggr : Node_Id; Dim : Pos) is
3169          Sub_Lo : constant Node_Id := Low_Bound (Aggregate_Bounds (Sub_Aggr));
3170          Sub_Hi : constant Node_Id := High_Bound (Aggregate_Bounds (Sub_Aggr));
3171          --  The bounds of this specific sub-aggregate.
3172
3173          Aggr_Lo : constant Node_Id := Aggr_Low (Dim);
3174          Aggr_Hi : constant Node_Id := Aggr_High (Dim);
3175          --  The bounds of the aggregate for this dimension
3176
3177          Ind_Typ : constant Entity_Id := Aggr_Index_Typ (Dim);
3178          --  The index type for this dimension.
3179
3180          Cond  : Node_Id := Empty;
3181
3182          Assoc : Node_Id;
3183          Expr  : Node_Id;
3184
3185       begin
3186          --  If index checks are on generate the test
3187          --
3188          --    [constraint_error when
3189          --      Aggr_Lo /= Sub_Lo or else Aggr_Hi /= Sub_Hi]
3190          --
3191          --  As an optimization try to see if some tests are trivially vacuos
3192          --  because we are comparing an expression against itself. Also for
3193          --  the first dimension the test is trivially vacuous because there
3194          --  is just one aggregate for dimension 1.
3195
3196          if Index_Checks_Suppressed (Ind_Typ) then
3197             Cond := Empty;
3198
3199          elsif Dim = 1
3200            or else (Aggr_Lo = Sub_Lo and then Aggr_Hi = Sub_Hi)
3201          then
3202             Cond := Empty;
3203
3204          elsif Aggr_Hi = Sub_Hi then
3205             Cond :=
3206               Make_Op_Ne (Loc,
3207                 Left_Opnd  => Duplicate_Subexpr_Move_Checks (Aggr_Lo),
3208                 Right_Opnd => Duplicate_Subexpr_Move_Checks (Sub_Lo));
3209
3210          elsif Aggr_Lo = Sub_Lo then
3211             Cond :=
3212               Make_Op_Ne (Loc,
3213                 Left_Opnd  => Duplicate_Subexpr_Move_Checks (Aggr_Hi),
3214                 Right_Opnd => Duplicate_Subexpr_Move_Checks (Sub_Hi));
3215
3216          else
3217             Cond :=
3218               Make_Or_Else (Loc,
3219                 Left_Opnd =>
3220                   Make_Op_Ne (Loc,
3221                     Left_Opnd  => Duplicate_Subexpr_Move_Checks (Aggr_Lo),
3222                     Right_Opnd => Duplicate_Subexpr_Move_Checks (Sub_Lo)),
3223
3224                 Right_Opnd =>
3225                   Make_Op_Ne (Loc,
3226                     Left_Opnd  => Duplicate_Subexpr (Aggr_Hi),
3227                     Right_Opnd => Duplicate_Subexpr (Sub_Hi)));
3228          end if;
3229
3230          if Present (Cond) then
3231             Insert_Action (N,
3232               Make_Raise_Constraint_Error (Loc,
3233                 Condition => Cond,
3234                 Reason    => CE_Length_Check_Failed));
3235          end if;
3236
3237          --  Now look inside the sub-aggregate to see if there is more work
3238
3239          if Dim < Aggr_Dimension then
3240
3241             --  Process positional components
3242
3243             if Present (Expressions (Sub_Aggr)) then
3244                Expr := First (Expressions (Sub_Aggr));
3245                while Present (Expr) loop
3246                   Check_Same_Aggr_Bounds (Expr, Dim + 1);
3247                   Next (Expr);
3248                end loop;
3249             end if;
3250
3251             --  Process component associations
3252
3253             if Present (Component_Associations (Sub_Aggr)) then
3254                Assoc := First (Component_Associations (Sub_Aggr));
3255                while Present (Assoc) loop
3256                   Expr := Expression (Assoc);
3257                   Check_Same_Aggr_Bounds (Expr, Dim + 1);
3258                   Next (Assoc);
3259                end loop;
3260             end if;
3261          end if;
3262       end Check_Same_Aggr_Bounds;
3263
3264       ----------------------------
3265       -- Compute_Others_Present --
3266       ----------------------------
3267
3268       procedure Compute_Others_Present (Sub_Aggr : Node_Id; Dim : Pos) is
3269          Assoc : Node_Id;
3270          Expr  : Node_Id;
3271
3272       begin
3273          if Present (Component_Associations (Sub_Aggr)) then
3274             Assoc := Last (Component_Associations (Sub_Aggr));
3275
3276             if Nkind (First (Choices (Assoc))) = N_Others_Choice then
3277                Others_Present (Dim) := True;
3278             end if;
3279          end if;
3280
3281          --  Now look inside the sub-aggregate to see if there is more work
3282
3283          if Dim < Aggr_Dimension then
3284
3285             --  Process positional components
3286
3287             if Present (Expressions (Sub_Aggr)) then
3288                Expr := First (Expressions (Sub_Aggr));
3289                while Present (Expr) loop
3290                   Compute_Others_Present (Expr, Dim + 1);
3291                   Next (Expr);
3292                end loop;
3293             end if;
3294
3295             --  Process component associations
3296
3297             if Present (Component_Associations (Sub_Aggr)) then
3298                Assoc := First (Component_Associations (Sub_Aggr));
3299                while Present (Assoc) loop
3300                   Expr := Expression (Assoc);
3301                   Compute_Others_Present (Expr, Dim + 1);
3302                   Next (Assoc);
3303                end loop;
3304             end if;
3305          end if;
3306       end Compute_Others_Present;
3307
3308       ------------------------
3309       -- Has_Address_Clause --
3310       ------------------------
3311
3312       function Has_Address_Clause (D : Node_Id) return Boolean is
3313          Id   : constant Entity_Id := Defining_Identifier (D);
3314          Decl : Node_Id := Next (D);
3315
3316       begin
3317          while Present (Decl) loop
3318             if Nkind (Decl) = N_At_Clause
3319                and then Chars (Identifier (Decl)) = Chars (Id)
3320             then
3321                return True;
3322
3323             elsif Nkind (Decl) = N_Attribute_Definition_Clause
3324                and then Chars (Decl) = Name_Address
3325                and then Chars (Name (Decl)) = Chars (Id)
3326             then
3327                return True;
3328             end if;
3329
3330             Next (Decl);
3331          end loop;
3332
3333          return False;
3334       end Has_Address_Clause;
3335
3336       ------------------------
3337       -- In_Place_Assign_OK --
3338       ------------------------
3339
3340       function In_Place_Assign_OK return Boolean is
3341          Aggr_In : Node_Id;
3342          Aggr_Lo : Node_Id;
3343          Aggr_Hi : Node_Id;
3344          Obj_In  : Node_Id;
3345          Obj_Lo  : Node_Id;
3346          Obj_Hi  : Node_Id;
3347
3348          function Is_Others_Aggregate (Aggr : Node_Id) return Boolean;
3349          --   Aggregates that consist of a single Others choice are safe
3350          --  if the single expression is.
3351
3352          function Safe_Aggregate (Aggr : Node_Id) return Boolean;
3353          --  Check recursively that each component of a (sub)aggregate does
3354          --  not depend on the variable being assigned to.
3355
3356          function Safe_Component (Expr : Node_Id) return Boolean;
3357          --  Verify that an expression cannot depend on the variable being
3358          --  assigned to. Room for improvement here (but less than before).
3359
3360          -------------------------
3361          -- Is_Others_Aggregate --
3362          -------------------------
3363
3364          function Is_Others_Aggregate (Aggr : Node_Id) return Boolean is
3365          begin
3366             return No (Expressions (Aggr))
3367               and then Nkind
3368                 (First (Choices (First (Component_Associations (Aggr)))))
3369                   = N_Others_Choice;
3370          end Is_Others_Aggregate;
3371
3372          --------------------
3373          -- Safe_Aggregate --
3374          --------------------
3375
3376          function Safe_Aggregate (Aggr : Node_Id) return Boolean is
3377             Expr : Node_Id;
3378
3379          begin
3380             if Present (Expressions (Aggr)) then
3381                Expr := First (Expressions (Aggr));
3382
3383                while Present (Expr) loop
3384                   if Nkind (Expr) = N_Aggregate then
3385                      if not Safe_Aggregate (Expr) then
3386                         return False;
3387                      end if;
3388
3389                   elsif not Safe_Component (Expr) then
3390                      return False;
3391                   end if;
3392
3393                   Next (Expr);
3394                end loop;
3395             end if;
3396
3397             if Present (Component_Associations (Aggr)) then
3398                Expr := First (Component_Associations (Aggr));
3399
3400                while Present (Expr) loop
3401                   if Nkind (Expression (Expr)) = N_Aggregate then
3402                      if not Safe_Aggregate (Expression (Expr)) then
3403                         return False;
3404                      end if;
3405
3406                   elsif not Safe_Component (Expression (Expr)) then
3407                      return False;
3408                   end if;
3409
3410                   Next (Expr);
3411                end loop;
3412             end if;
3413
3414             return True;
3415          end Safe_Aggregate;
3416
3417          --------------------
3418          -- Safe_Component --
3419          --------------------
3420
3421          function Safe_Component (Expr : Node_Id) return Boolean is
3422             Comp : Node_Id := Expr;
3423
3424             function Check_Component (Comp : Node_Id) return Boolean;
3425             --  Do the recursive traversal, after copy.
3426
3427             ---------------------
3428             -- Check_Component --
3429             ---------------------
3430
3431             function Check_Component (Comp : Node_Id) return Boolean is
3432             begin
3433                if Is_Overloaded (Comp) then
3434                   return False;
3435                end if;
3436
3437                return Compile_Time_Known_Value (Comp)
3438
3439                  or else (Is_Entity_Name (Comp)
3440                            and then  Present (Entity (Comp))
3441                            and then No (Renamed_Object (Entity (Comp))))
3442
3443                  or else (Nkind (Comp) = N_Attribute_Reference
3444                            and then Check_Component (Prefix (Comp)))
3445
3446                  or else (Nkind (Comp) in N_Binary_Op
3447                            and then Check_Component (Left_Opnd  (Comp))
3448                            and then Check_Component (Right_Opnd (Comp)))
3449
3450                  or else (Nkind (Comp) in N_Unary_Op
3451                            and then Check_Component (Right_Opnd (Comp)))
3452
3453                  or else (Nkind (Comp) = N_Selected_Component
3454                            and then Check_Component (Prefix (Comp)));
3455             end Check_Component;
3456
3457          --  Start of processing for Safe_Component
3458
3459          begin
3460             --  If the component appears in an association that may
3461             --  correspond to more than one element, it is not analyzed
3462             --  before the expansion into assignments, to avoid side effects.
3463             --  We analyze, but do not resolve the copy, to obtain sufficient
3464             --  entity information for the checks that follow. If component is
3465             --  overloaded we assume an unsafe function call.
3466
3467             if not Analyzed (Comp) then
3468                if Is_Overloaded (Expr) then
3469                   return False;
3470
3471                elsif Nkind (Expr) = N_Aggregate
3472                   and then not Is_Others_Aggregate (Expr)
3473                then
3474                   return False;
3475
3476                elsif Nkind (Expr) = N_Allocator then
3477                   --  For now, too complex to analyze.
3478
3479                   return False;
3480                end if;
3481
3482                Comp := New_Copy_Tree (Expr);
3483                Set_Parent (Comp, Parent (Expr));
3484                Analyze (Comp);
3485             end if;
3486
3487             if Nkind (Comp) = N_Aggregate then
3488                return Safe_Aggregate (Comp);
3489             else
3490                return Check_Component (Comp);
3491             end if;
3492          end Safe_Component;
3493
3494       --  Start of processing for In_Place_Assign_OK
3495
3496       begin
3497          if Present (Component_Associations (N)) then
3498
3499             --  On assignment, sliding can take place, so we cannot do the
3500             --  assignment in place unless the bounds of the aggregate are
3501             --  statically equal to those of the target.
3502
3503             --  If the aggregate is given by an others choice, the bounds
3504             --  are derived from the left-hand side, and the assignment is
3505             --  safe if the expression is.
3506
3507             if Is_Others_Aggregate (N) then
3508                return
3509                  Safe_Component
3510                   (Expression (First (Component_Associations (N))));
3511             end if;
3512
3513             Aggr_In := First_Index (Etype (N));
3514             Obj_In  := First_Index (Etype (Name (Parent (N))));
3515
3516             while Present (Aggr_In) loop
3517                Get_Index_Bounds (Aggr_In, Aggr_Lo, Aggr_Hi);
3518                Get_Index_Bounds (Obj_In, Obj_Lo, Obj_Hi);
3519
3520                if not Compile_Time_Known_Value (Aggr_Lo)
3521                  or else not Compile_Time_Known_Value (Aggr_Hi)
3522                  or else not Compile_Time_Known_Value (Obj_Lo)
3523                  or else not Compile_Time_Known_Value (Obj_Hi)
3524                  or else Expr_Value (Aggr_Lo) /= Expr_Value (Obj_Lo)
3525                  or else Expr_Value (Aggr_Hi) /= Expr_Value (Obj_Hi)
3526                then
3527                   return False;
3528                end if;
3529
3530                Next_Index (Aggr_In);
3531                Next_Index (Obj_In);
3532             end loop;
3533          end if;
3534
3535          --  Now check the component values themselves.
3536
3537          return Safe_Aggregate (N);
3538       end In_Place_Assign_OK;
3539
3540       ----------------
3541       -- Must_Slide --
3542       ----------------
3543
3544       function Must_Slide (N : Node_Id; Typ : Entity_Id) return Boolean
3545       is
3546          Obj_Type : constant Entity_Id :=
3547                       Etype (Defining_Identifier (Parent (N)));
3548
3549          L1, L2, H1, H2 : Node_Id;
3550
3551       begin
3552          --  No sliding if the type of the object is not established yet, if
3553          --  it is an unconstrained type whose actual subtype comes from the
3554          --  aggregate, or if the two types are identical.
3555
3556          if not Is_Array_Type (Obj_Type) then
3557             return False;
3558
3559          elsif not Is_Constrained (Obj_Type) then
3560             return False;
3561
3562          elsif Typ = Obj_Type then
3563             return False;
3564
3565          else
3566             --  Sliding can only occur along the first dimension
3567
3568             Get_Index_Bounds (First_Index (Typ), L1, H1);
3569             Get_Index_Bounds (First_Index (Obj_Type), L2, H2);
3570
3571             if not Is_Static_Expression (L1)
3572               or else not Is_Static_Expression (L2)
3573               or else not Is_Static_Expression (H1)
3574               or else not Is_Static_Expression (H2)
3575             then
3576                return False;
3577             else
3578                return Expr_Value (L1) /= Expr_Value (L2)
3579                  or else Expr_Value (H1) /= Expr_Value (H2);
3580             end if;
3581          end if;
3582       end Must_Slide;
3583
3584       ------------------
3585       -- Others_Check --
3586       ------------------
3587
3588       procedure Others_Check (Sub_Aggr : Node_Id; Dim : Pos) is
3589          Aggr_Lo : constant Node_Id := Aggr_Low (Dim);
3590          Aggr_Hi : constant Node_Id := Aggr_High (Dim);
3591          --  The bounds of the aggregate for this dimension.
3592
3593          Ind_Typ : constant Entity_Id := Aggr_Index_Typ (Dim);
3594          --  The index type for this dimension.
3595
3596          Need_To_Check : Boolean := False;
3597
3598          Choices_Lo : Node_Id := Empty;
3599          Choices_Hi : Node_Id := Empty;
3600          --  The lowest and highest discrete choices for a named sub-aggregate
3601
3602          Nb_Choices : Int := -1;
3603          --  The number of discrete non-others choices in this sub-aggregate
3604
3605          Nb_Elements : Uint := Uint_0;
3606          --  The number of elements in a positional aggregate
3607
3608          Cond : Node_Id := Empty;
3609
3610          Assoc  : Node_Id;
3611          Choice : Node_Id;
3612          Expr   : Node_Id;
3613
3614       begin
3615          --  Check if we have an others choice. If we do make sure that this
3616          --  sub-aggregate contains at least one element in addition to the
3617          --  others choice.
3618
3619          if Range_Checks_Suppressed (Ind_Typ) then
3620             Need_To_Check := False;
3621
3622          elsif Present (Expressions (Sub_Aggr))
3623            and then Present (Component_Associations (Sub_Aggr))
3624          then
3625             Need_To_Check := True;
3626
3627          elsif Present (Component_Associations (Sub_Aggr)) then
3628             Assoc := Last (Component_Associations (Sub_Aggr));
3629
3630             if Nkind (First (Choices (Assoc))) /= N_Others_Choice then
3631                Need_To_Check := False;
3632
3633             else
3634                --  Count the number of discrete choices. Start with -1
3635                --  because the others choice does not count.
3636
3637                Nb_Choices := -1;
3638                Assoc := First (Component_Associations (Sub_Aggr));
3639                while Present (Assoc) loop
3640                   Choice := First (Choices (Assoc));
3641                   while Present (Choice) loop
3642                      Nb_Choices := Nb_Choices + 1;
3643                      Next (Choice);
3644                   end loop;
3645
3646                   Next (Assoc);
3647                end loop;
3648
3649                --  If there is only an others choice nothing to do
3650
3651                Need_To_Check := (Nb_Choices > 0);
3652             end if;
3653
3654          else
3655             Need_To_Check := False;
3656          end if;
3657
3658          --  If we are dealing with a positional sub-aggregate with an
3659          --  others choice then compute the number or positional elements.
3660
3661          if Need_To_Check and then Present (Expressions (Sub_Aggr)) then
3662             Expr := First (Expressions (Sub_Aggr));
3663             Nb_Elements := Uint_0;
3664             while Present (Expr) loop
3665                Nb_Elements := Nb_Elements + 1;
3666                Next (Expr);
3667             end loop;
3668
3669          --  If the aggregate contains discrete choices and an others choice
3670          --  compute the smallest and largest discrete choice values.
3671
3672          elsif Need_To_Check then
3673             Compute_Choices_Lo_And_Choices_Hi : declare
3674
3675                Table : Case_Table_Type (1 .. Nb_Choices);
3676                --  Used to sort all the different choice values
3677
3678                J    : Pos := 1;
3679                Low  : Node_Id;
3680                High : Node_Id;
3681
3682             begin
3683                Assoc := First (Component_Associations (Sub_Aggr));
3684                while Present (Assoc) loop
3685                   Choice := First (Choices (Assoc));
3686                   while Present (Choice) loop
3687                      if Nkind (Choice) = N_Others_Choice then
3688                         exit;
3689                      end if;
3690
3691                      Get_Index_Bounds (Choice, Low, High);
3692                      Table (J).Choice_Lo := Low;
3693                      Table (J).Choice_Hi := High;
3694
3695                      J := J + 1;
3696                      Next (Choice);
3697                   end loop;
3698
3699                   Next (Assoc);
3700                end loop;
3701
3702                --  Sort the discrete choices
3703
3704                Sort_Case_Table (Table);
3705
3706                Choices_Lo := Table (1).Choice_Lo;
3707                Choices_Hi := Table (Nb_Choices).Choice_Hi;
3708             end Compute_Choices_Lo_And_Choices_Hi;
3709          end if;
3710
3711          --  If no others choice in this sub-aggregate, or the aggregate
3712          --  comprises only an others choice, nothing to do.
3713
3714          if not Need_To_Check then
3715             Cond := Empty;
3716
3717          --  If we are dealing with an aggregate containing an others
3718          --  choice and positional components, we generate the following test:
3719          --
3720          --    if Ind_Typ'Pos (Aggr_Lo) + (Nb_Elements - 1) >
3721          --            Ind_Typ'Pos (Aggr_Hi)
3722          --    then
3723          --       raise Constraint_Error;
3724          --    end if;
3725
3726          elsif Nb_Elements > Uint_0 then
3727             Cond :=
3728               Make_Op_Gt (Loc,
3729                 Left_Opnd  =>
3730                   Make_Op_Add (Loc,
3731                     Left_Opnd  =>
3732                       Make_Attribute_Reference (Loc,
3733                         Prefix         => New_Reference_To (Ind_Typ, Loc),
3734                         Attribute_Name => Name_Pos,
3735                         Expressions    =>
3736                           New_List
3737                             (Duplicate_Subexpr_Move_Checks (Aggr_Lo))),
3738                     Right_Opnd => Make_Integer_Literal (Loc, Nb_Elements - 1)),
3739
3740                 Right_Opnd =>
3741                   Make_Attribute_Reference (Loc,
3742                     Prefix         => New_Reference_To (Ind_Typ, Loc),
3743                     Attribute_Name => Name_Pos,
3744                     Expressions    => New_List (
3745                       Duplicate_Subexpr_Move_Checks (Aggr_Hi))));
3746
3747          --  If we are dealing with an aggregate containing an others
3748          --  choice and discrete choices we generate the following test:
3749          --
3750          --    [constraint_error when
3751          --      Choices_Lo < Aggr_Lo or else Choices_Hi > Aggr_Hi];
3752
3753          else
3754             Cond :=
3755               Make_Or_Else (Loc,
3756                 Left_Opnd =>
3757                   Make_Op_Lt (Loc,
3758                     Left_Opnd  =>
3759                       Duplicate_Subexpr_Move_Checks (Choices_Lo),
3760                     Right_Opnd =>
3761                       Duplicate_Subexpr_Move_Checks (Aggr_Lo)),
3762
3763                 Right_Opnd =>
3764                   Make_Op_Gt (Loc,
3765                     Left_Opnd  =>
3766                       Duplicate_Subexpr (Choices_Hi),
3767                     Right_Opnd =>
3768                       Duplicate_Subexpr (Aggr_Hi)));
3769          end if;
3770
3771          if Present (Cond) then
3772             Insert_Action (N,
3773               Make_Raise_Constraint_Error (Loc,
3774                 Condition => Cond,
3775                 Reason    => CE_Length_Check_Failed));
3776          end if;
3777
3778          --  Now look inside the sub-aggregate to see if there is more work
3779
3780          if Dim < Aggr_Dimension then
3781
3782             --  Process positional components
3783
3784             if Present (Expressions (Sub_Aggr)) then
3785                Expr := First (Expressions (Sub_Aggr));
3786                while Present (Expr) loop
3787                   Others_Check (Expr, Dim + 1);
3788                   Next (Expr);
3789                end loop;
3790             end if;
3791
3792             --  Process component associations
3793
3794             if Present (Component_Associations (Sub_Aggr)) then
3795                Assoc := First (Component_Associations (Sub_Aggr));
3796                while Present (Assoc) loop
3797                   Expr := Expression (Assoc);
3798                   Others_Check (Expr, Dim + 1);
3799                   Next (Assoc);
3800                end loop;
3801             end if;
3802          end if;
3803       end Others_Check;
3804
3805       --  Remaining Expand_Array_Aggregate variables
3806
3807       Tmp : Entity_Id;
3808       --  Holds the temporary aggregate value
3809
3810       Tmp_Decl : Node_Id;
3811       --  Holds the declaration of Tmp
3812
3813       Aggr_Code   : List_Id;
3814       Parent_Node : Node_Id;
3815       Parent_Kind : Node_Kind;
3816
3817    --  Start of processing for Expand_Array_Aggregate
3818
3819    begin
3820       --  Do not touch the special aggregates of attributes used for Asm calls
3821
3822       if Is_RTE (Ctyp, RE_Asm_Input_Operand)
3823         or else Is_RTE (Ctyp, RE_Asm_Output_Operand)
3824       then
3825          return;
3826       end if;
3827
3828       --  If the semantic analyzer has determined that aggregate N will raise
3829       --  Constraint_Error at run-time, then the aggregate node has been
3830       --  replaced with an N_Raise_Constraint_Error node and we should
3831       --  never get here.
3832
3833       pragma Assert (not Raises_Constraint_Error (N));
3834
3835       --  STEP 1a.
3836
3837       --  Check that the index range defined by aggregate bounds is
3838       --  compatible with corresponding index subtype.
3839
3840       Index_Compatibility_Check : declare
3841          Aggr_Index_Range : Node_Id := First_Index (Typ);
3842          --  The current aggregate index range
3843
3844          Index_Constraint : Node_Id := First_Index (Etype (Typ));
3845          --  The corresponding index constraint against which we have to
3846          --  check the above aggregate index range.
3847
3848       begin
3849          Compute_Others_Present (N, 1);
3850
3851          for J in 1 .. Aggr_Dimension loop
3852             --  There is no need to emit a check if an others choice is
3853             --  present for this array aggregate dimension since in this
3854             --  case one of N's sub-aggregates has taken its bounds from the
3855             --  context and these bounds must have been checked already. In
3856             --  addition all sub-aggregates corresponding to the same
3857             --  dimension must all have the same bounds (checked in (c) below).
3858
3859             if not Range_Checks_Suppressed (Etype (Index_Constraint))
3860               and then not Others_Present (J)
3861             then
3862                --  We don't use Checks.Apply_Range_Check here because it
3863                --  emits a spurious check. Namely it checks that the range
3864                --  defined by the aggregate bounds is non empty. But we know
3865                --  this already if we get here.
3866
3867                Check_Bounds (Aggr_Index_Range, Index_Constraint);
3868             end if;
3869
3870             --  Save the low and high bounds of the aggregate index as well
3871             --  as the index type for later use in checks (b) and (c) below.
3872
3873             Aggr_Low  (J) := Low_Bound (Aggr_Index_Range);
3874             Aggr_High (J) := High_Bound (Aggr_Index_Range);
3875
3876             Aggr_Index_Typ (J) := Etype (Index_Constraint);
3877
3878             Next_Index (Aggr_Index_Range);
3879             Next_Index (Index_Constraint);
3880          end loop;
3881       end Index_Compatibility_Check;
3882
3883       --  STEP 1b.
3884
3885       --  If an others choice is present check that no aggregate
3886       --  index is outside the bounds of the index constraint.
3887
3888       Others_Check (N, 1);
3889
3890       --  STEP 1c.
3891
3892       --  For multidimensional arrays make sure that all subaggregates
3893       --  corresponding to the same dimension have the same bounds.
3894
3895       if Aggr_Dimension > 1 then
3896          Check_Same_Aggr_Bounds (N, 1);
3897       end if;
3898
3899       --  STEP 2.
3900
3901       --  Here we test for is packed array aggregate that we can handle
3902       --  at compile time. If so, return with transformation done. Note
3903       --  that we do this even if the aggregate is nested, because once
3904       --  we have done this processing, there is no more nested aggregate!
3905
3906       if Packed_Array_Aggregate_Handled (N) then
3907          return;
3908       end if;
3909
3910       --  At this point we try to convert to positional form
3911
3912       Convert_To_Positional (N);
3913
3914       --  if the result is no longer an aggregate (e.g. it may be a string
3915       --  literal, or a temporary which has the needed value), then we are
3916       --  done, since there is no longer a nested aggregate.
3917
3918       if Nkind (N) /= N_Aggregate then
3919          return;
3920
3921       --  We are also done if the result is an analyzed aggregate
3922       --  This case could use more comments ???
3923
3924       elsif Analyzed (N)
3925         and then N /= Original_Node (N)
3926       then
3927          return;
3928       end if;
3929
3930       --  Now see if back end processing is possible
3931
3932       if Backend_Processing_Possible (N) then
3933
3934          --  If the aggregate is static but the constraints are not, build
3935          --  a static subtype for the aggregate, so that Gigi can place it
3936          --  in static memory. Perform an unchecked_conversion to the non-
3937          --  static type imposed by the context.
3938
3939          declare
3940             Itype      : constant Entity_Id := Etype (N);
3941             Index      : Node_Id;
3942             Needs_Type : Boolean := False;
3943
3944          begin
3945             Index := First_Index (Itype);
3946
3947             while Present (Index) loop
3948                if not Is_Static_Subtype (Etype (Index)) then
3949                   Needs_Type := True;
3950                   exit;
3951                else
3952                   Next_Index (Index);
3953                end if;
3954             end loop;
3955
3956             if Needs_Type then
3957                Build_Constrained_Type (Positional => True);
3958                Rewrite (N, Unchecked_Convert_To (Itype, N));
3959                Analyze (N);
3960             end if;
3961          end;
3962
3963          return;
3964       end if;
3965
3966       --  STEP 3.
3967
3968       --  Delay expansion for nested aggregates it will be taken care of
3969       --  when the parent aggregate is expanded
3970
3971       Parent_Node := Parent (N);
3972       Parent_Kind := Nkind (Parent_Node);
3973
3974       if Parent_Kind = N_Qualified_Expression then
3975          Parent_Node := Parent (Parent_Node);
3976          Parent_Kind := Nkind (Parent_Node);
3977       end if;
3978
3979       if Parent_Kind = N_Aggregate
3980         or else Parent_Kind = N_Extension_Aggregate
3981         or else Parent_Kind = N_Component_Association
3982         or else (Parent_Kind = N_Object_Declaration
3983                   and then Controlled_Type (Typ))
3984         or else (Parent_Kind = N_Assignment_Statement
3985                   and then Inside_Init_Proc)
3986       then
3987          Set_Expansion_Delayed (N);
3988          return;
3989       end if;
3990
3991       --  STEP 4.
3992
3993       --  Look if in place aggregate expansion is possible
3994
3995       --  For object declarations we build the aggregate in place, unless
3996       --  the array is bit-packed or the component is controlled.
3997
3998       --  For assignments we do the assignment in place if all the component
3999       --  associations have compile-time known values. For other cases we
4000       --  create a temporary. The analysis for safety of on-line assignment
4001       --  is delicate, i.e. we don't know how to do it fully yet ???
4002
4003       if Requires_Transient_Scope (Typ) then
4004          Establish_Transient_Scope
4005            (N, Sec_Stack => Has_Controlled_Component (Typ));
4006       end if;
4007
4008       if Has_Default_Init_Comps (N) then
4009          Maybe_In_Place_OK := False;
4010       else
4011          Maybe_In_Place_OK :=
4012            Comes_From_Source (N)
4013              and then Nkind (Parent (N)) = N_Assignment_Statement
4014              and then not Is_Bit_Packed_Array (Typ)
4015              and then not Has_Controlled_Component (Typ)
4016              and then In_Place_Assign_OK;
4017       end if;
4018
4019       if not Has_Default_Init_Comps (N)
4020          and then Comes_From_Source (Parent (N))
4021          and then Nkind (Parent (N)) = N_Object_Declaration
4022          and then not Must_Slide (N, Typ)
4023          and then N = Expression (Parent (N))
4024          and then not Is_Bit_Packed_Array (Typ)
4025          and then not Has_Controlled_Component (Typ)
4026          and then not Has_Address_Clause (Parent (N))
4027       then
4028          Tmp := Defining_Identifier (Parent (N));
4029          Set_No_Initialization (Parent (N));
4030          Set_Expression (Parent (N), Empty);
4031
4032          --  Set the type of the entity, for use in the analysis of the
4033          --  subsequent indexed assignments. If the nominal type is not
4034          --  constrained, build a subtype from the known bounds of the
4035          --  aggregate. If the declaration has a subtype mark, use it,
4036          --  otherwise use the itype of the aggregate.
4037
4038          if not Is_Constrained (Typ) then
4039             Build_Constrained_Type (Positional => False);
4040          elsif Is_Entity_Name (Object_Definition (Parent (N)))
4041            and then Is_Constrained (Entity (Object_Definition (Parent (N))))
4042          then
4043             Set_Etype (Tmp, Entity (Object_Definition (Parent (N))));
4044          else
4045             Set_Size_Known_At_Compile_Time (Typ, False);
4046             Set_Etype (Tmp, Typ);
4047          end if;
4048
4049       elsif Maybe_In_Place_OK
4050         and then Is_Entity_Name (Name (Parent (N)))
4051       then
4052          Tmp := Entity (Name (Parent (N)));
4053
4054          if Etype (Tmp) /= Etype (N) then
4055             Apply_Length_Check (N, Etype (Tmp));
4056
4057             if Nkind (N) = N_Raise_Constraint_Error then
4058
4059                --  Static error, nothing further to expand
4060
4061                return;
4062             end if;
4063          end if;
4064
4065       elsif Maybe_In_Place_OK
4066         and then Nkind (Name (Parent (N))) = N_Explicit_Dereference
4067         and then Is_Entity_Name (Prefix (Name (Parent (N))))
4068       then
4069          Tmp := Name (Parent (N));
4070
4071          if Etype (Tmp) /= Etype (N) then
4072             Apply_Length_Check (N, Etype (Tmp));
4073          end if;
4074
4075       elsif Maybe_In_Place_OK
4076         and then Nkind (Name (Parent (N))) = N_Slice
4077         and then Safe_Slice_Assignment (N)
4078       then
4079          --  Safe_Slice_Assignment rewrites assignment as a loop
4080
4081          return;
4082
4083       --  Step 5
4084
4085       --  In place aggregate expansion is not possible
4086
4087       else
4088          Maybe_In_Place_OK := False;
4089          Tmp := Make_Defining_Identifier (Loc, New_Internal_Name ('A'));
4090          Tmp_Decl :=
4091            Make_Object_Declaration
4092              (Loc,
4093               Defining_Identifier => Tmp,
4094               Object_Definition   => New_Occurrence_Of (Typ, Loc));
4095          Set_No_Initialization (Tmp_Decl, True);
4096
4097          --  If we are within a loop, the temporary will be pushed on the
4098          --  stack at each iteration. If the aggregate is the expression for
4099          --  an allocator, it will be immediately copied to the heap and can
4100          --  be reclaimed at once. We create a transient scope around the
4101          --  aggregate for this purpose.
4102
4103          if Ekind (Current_Scope) = E_Loop
4104            and then Nkind (Parent (Parent (N))) = N_Allocator
4105          then
4106             Establish_Transient_Scope (N, False);
4107          end if;
4108
4109          Insert_Action (N, Tmp_Decl);
4110       end if;
4111
4112       --  Construct and insert the aggregate code. We can safely suppress
4113       --  index checks because this code is guaranteed not to raise CE
4114       --  on index checks. However we should *not* suppress all checks.
4115
4116       declare
4117          Target : Node_Id;
4118
4119       begin
4120          if Nkind (Tmp) = N_Defining_Identifier then
4121             Target := New_Reference_To (Tmp, Loc);
4122
4123          else
4124
4125             if Has_Default_Init_Comps (N) then
4126
4127                --  Ada 2005 (AI-287): This case has not been analyzed???
4128
4129                raise Program_Error;
4130             end if;
4131
4132             --  Name in assignment is explicit dereference
4133
4134             Target := New_Copy (Tmp);
4135          end if;
4136
4137          Aggr_Code :=
4138            Build_Array_Aggr_Code (N,
4139              Ctype       => Ctyp,
4140              Index       => First_Index (Typ),
4141              Into        => Target,
4142              Scalar_Comp => Is_Scalar_Type (Ctyp));
4143       end;
4144
4145       if Comes_From_Source (Tmp) then
4146          Insert_Actions_After (Parent (N), Aggr_Code);
4147
4148       else
4149          Insert_Actions (N, Aggr_Code);
4150       end if;
4151
4152       --  If the aggregate has been assigned in place, remove the original
4153       --  assignment.
4154
4155       if Nkind (Parent (N)) = N_Assignment_Statement
4156         and then Maybe_In_Place_OK
4157       then
4158          Rewrite (Parent (N), Make_Null_Statement (Loc));
4159
4160       elsif Nkind (Parent (N)) /= N_Object_Declaration
4161         or else Tmp /= Defining_Identifier (Parent (N))
4162       then
4163          Rewrite (N, New_Occurrence_Of (Tmp, Loc));
4164          Analyze_And_Resolve (N, Typ);
4165       end if;
4166    end Expand_Array_Aggregate;
4167
4168    ------------------------
4169    -- Expand_N_Aggregate --
4170    ------------------------
4171
4172    procedure Expand_N_Aggregate (N : Node_Id) is
4173    begin
4174       if Is_Record_Type (Etype (N)) then
4175          Expand_Record_Aggregate (N);
4176       else
4177          Expand_Array_Aggregate (N);
4178       end if;
4179
4180    exception
4181       when RE_Not_Available =>
4182          return;
4183    end Expand_N_Aggregate;
4184
4185    ----------------------------------
4186    -- Expand_N_Extension_Aggregate --
4187    ----------------------------------
4188
4189    --  If the ancestor part is an expression, add a component association for
4190    --  the parent field. If the type of the ancestor part is not the direct
4191    --  parent of the expected type,  build recursively the needed ancestors.
4192    --  If the ancestor part is a subtype_mark, replace aggregate with a decla-
4193    --  ration for a temporary of the expected type, followed by individual
4194    --  assignments to the given components.
4195
4196    procedure Expand_N_Extension_Aggregate (N : Node_Id) is
4197       Loc : constant Source_Ptr := Sloc  (N);
4198       A   : constant Node_Id    := Ancestor_Part (N);
4199       Typ : constant Entity_Id  := Etype (N);
4200
4201    begin
4202       --  If the ancestor is a subtype mark, an init proc must be called
4203       --  on the resulting object which thus has to be materialized in
4204       --  the front-end
4205
4206       if Is_Entity_Name (A) and then Is_Type (Entity (A)) then
4207          Convert_To_Assignments (N, Typ);
4208
4209       --  The extension aggregate is transformed into a record aggregate
4210       --  of the following form (c1 and c2 are inherited components)
4211
4212       --   (Exp with c3 => a, c4 => b)
4213       --      ==> (c1 => Exp.c1, c2 => Exp.c2, c1 => a, c2 => b)
4214
4215       else
4216          Set_Etype (N, Typ);
4217
4218          --  No tag is needed in the case of Java_VM
4219
4220          if Java_VM then
4221             Expand_Record_Aggregate (N,
4222               Parent_Expr => A);
4223          else
4224             Expand_Record_Aggregate (N,
4225               Orig_Tag    => New_Occurrence_Of (Access_Disp_Table (Typ), Loc),
4226               Parent_Expr => A);
4227          end if;
4228       end if;
4229
4230    exception
4231       when RE_Not_Available =>
4232          return;
4233    end Expand_N_Extension_Aggregate;
4234
4235    -----------------------------
4236    -- Expand_Record_Aggregate --
4237    -----------------------------
4238
4239    procedure Expand_Record_Aggregate
4240      (N           : Node_Id;
4241       Orig_Tag    : Node_Id := Empty;
4242       Parent_Expr : Node_Id := Empty)
4243    is
4244       Loc      : constant Source_Ptr := Sloc  (N);
4245       Comps    : constant List_Id    := Component_Associations (N);
4246       Typ      : constant Entity_Id  := Etype (N);
4247       Base_Typ : constant Entity_Id  := Base_Type (Typ);
4248
4249       function Has_Delayed_Nested_Aggregate_Or_Tagged_Comps return Boolean;
4250       --  Checks the presence of a nested aggregate which needs Late_Expansion
4251       --  or the presence of tagged components which may need tag adjustment.
4252
4253       --------------------------------------------------
4254       -- Has_Delayed_Nested_Aggregate_Or_Tagged_Comps --
4255       --------------------------------------------------
4256
4257       function Has_Delayed_Nested_Aggregate_Or_Tagged_Comps return Boolean is
4258          C      : Node_Id;
4259          Expr_Q : Node_Id;
4260
4261       begin
4262          if No (Comps) then
4263             return False;
4264          end if;
4265
4266          C := First (Comps);
4267          while Present (C) loop
4268             if Nkind (Expression (C)) = N_Qualified_Expression then
4269                Expr_Q := Expression (Expression (C));
4270             else
4271                Expr_Q := Expression (C);
4272             end if;
4273
4274             --  Return true if the aggregate has any associations for
4275             --  tagged components that may require tag adjustment.
4276             --  These are cases where the source expression may have
4277             --  a tag that could differ from the component tag (e.g.,
4278             --  can occur for type conversions and formal parameters).
4279             --  (Tag adjustment is not needed if Java_VM because object
4280             --  tags are implicit in the JVM.)
4281
4282             if Is_Tagged_Type (Etype (Expr_Q))
4283               and then (Nkind (Expr_Q) = N_Type_Conversion
4284                 or else (Is_Entity_Name (Expr_Q)
4285                           and then Ekind (Entity (Expr_Q)) in Formal_Kind))
4286               and then not Java_VM
4287             then
4288                return True;
4289             end if;
4290
4291             if Is_Delayed_Aggregate (Expr_Q) then
4292                return True;
4293             end if;
4294
4295             Next (C);
4296          end loop;
4297
4298          return False;
4299       end Has_Delayed_Nested_Aggregate_Or_Tagged_Comps;
4300
4301       --  Remaining Expand_Record_Aggregate variables
4302
4303       Tag_Value : Node_Id;
4304       Comp      : Entity_Id;
4305       New_Comp  : Node_Id;
4306
4307    --  Start of processing for Expand_Record_Aggregate
4308
4309    begin
4310       --  If the aggregate is to be assigned to an atomic variable, we
4311       --  have to prevent a piecemeal assignment even if the aggregate
4312       --  is to be expanded. We create a temporary for the aggregate, and
4313       --  assign the temporary instead, so that the back end can generate
4314       --  an atomic move for it.
4315
4316       if Is_Atomic (Typ)
4317         and then (Nkind (Parent (N)) = N_Object_Declaration
4318                     or else Nkind (Parent (N)) = N_Assignment_Statement)
4319         and then Comes_From_Source (Parent (N))
4320       then
4321          Expand_Atomic_Aggregate (N, Typ);
4322          return;
4323       end if;
4324
4325       --  Gigi doesn't handle properly temporaries of variable size
4326       --  so we generate it in the front-end
4327
4328       if not Size_Known_At_Compile_Time (Typ) then
4329          Convert_To_Assignments (N, Typ);
4330
4331       --  Temporaries for controlled aggregates need to be attached to a
4332       --  final chain in order to be properly finalized, so it has to
4333       --  be created in the front-end
4334
4335       elsif Is_Controlled (Typ)
4336         or else Has_Controlled_Component (Base_Type (Typ))
4337       then
4338          Convert_To_Assignments (N, Typ);
4339
4340          --  Ada 2005 (AI-287): In case of default initialized components we
4341          --  convert the aggregate into assignments.
4342
4343       elsif Has_Default_Init_Comps (N) then
4344          Convert_To_Assignments (N, Typ);
4345
4346       elsif Has_Delayed_Nested_Aggregate_Or_Tagged_Comps then
4347          Convert_To_Assignments (N, Typ);
4348
4349       --  If an ancestor is private, some components are not inherited and
4350       --  we cannot expand into a record aggregate
4351
4352       elsif Has_Private_Ancestor (Typ) then
4353          Convert_To_Assignments (N, Typ);
4354
4355       --  ??? The following was done to compile fxacc00.ads in the ACVCs. Gigi
4356       --  is not able to handle the aggregate for Late_Request.
4357
4358       elsif Is_Tagged_Type (Typ) and then Has_Discriminants (Typ) then
4359          Convert_To_Assignments (N, Typ);
4360
4361       --  If some components are mutable, the size of the aggregate component
4362       --  may be disctinct from the default size of the type component, so
4363       --  we need to expand to insure that the back-end copies the proper
4364       --  size of the data.
4365
4366       elsif Has_Mutable_Components (Typ) then
4367          Convert_To_Assignments (N, Typ);
4368
4369       --  If the type involved has any non-bit aligned components, then
4370       --  we are not sure that the back end can handle this case correctly.
4371
4372       elsif Type_May_Have_Bit_Aligned_Components (Typ) then
4373          Convert_To_Assignments (N, Typ);
4374
4375       --  In all other cases we generate a proper aggregate that
4376       --  can be handled by gigi.
4377
4378       else
4379          --  If no discriminants, nothing special to do
4380
4381          if not Has_Discriminants (Typ) then
4382             null;
4383
4384          --  Case of discriminants present
4385
4386          elsif Is_Derived_Type (Typ) then
4387
4388             --  For untagged types,  non-stored discriminants are replaced
4389             --  with stored discriminants, which are the ones that gigi uses
4390             --  to describe the type and its components.
4391
4392             Generate_Aggregate_For_Derived_Type : declare
4393                Constraints  : constant List_Id := New_List;
4394                First_Comp   : Node_Id;
4395                Discriminant : Entity_Id;
4396                Decl         : Node_Id;
4397                Num_Disc     : Int := 0;
4398                Num_Gird     : Int := 0;
4399
4400                procedure Prepend_Stored_Values (T : Entity_Id);
4401                --  Scan the list of stored discriminants of the type, and
4402                --  add their values to the aggregate being built.
4403
4404                ---------------------------
4405                -- Prepend_Stored_Values --
4406                ---------------------------
4407
4408                procedure Prepend_Stored_Values (T : Entity_Id) is
4409                begin
4410                   Discriminant := First_Stored_Discriminant (T);
4411
4412                   while Present (Discriminant) loop
4413                      New_Comp :=
4414                        Make_Component_Association (Loc,
4415                          Choices    =>
4416                            New_List (New_Occurrence_Of (Discriminant, Loc)),
4417
4418                          Expression =>
4419                            New_Copy_Tree (
4420                              Get_Discriminant_Value (
4421                                  Discriminant,
4422                                  Typ,
4423                                  Discriminant_Constraint (Typ))));
4424
4425                      if No (First_Comp) then
4426                         Prepend_To (Component_Associations (N), New_Comp);
4427                      else
4428                         Insert_After (First_Comp, New_Comp);
4429                      end if;
4430
4431                      First_Comp := New_Comp;
4432                      Next_Stored_Discriminant (Discriminant);
4433                   end loop;
4434                end Prepend_Stored_Values;
4435
4436             --  Start of processing for Generate_Aggregate_For_Derived_Type
4437
4438             begin
4439                --  Remove the associations for the  discriminant of
4440                --  the derived type.
4441
4442                First_Comp := First (Component_Associations (N));
4443
4444                while Present (First_Comp) loop
4445                   Comp := First_Comp;
4446                   Next (First_Comp);
4447
4448                   if Ekind (Entity (First (Choices (Comp)))) =
4449                     E_Discriminant
4450                   then
4451                      Remove (Comp);
4452                      Num_Disc := Num_Disc + 1;
4453                   end if;
4454                end loop;
4455
4456                --  Insert stored discriminant associations in the correct
4457                --  order. If there are more stored discriminants than new
4458                --  discriminants, there is at least one new discriminant
4459                --  that constrains more than one of the stored discriminants.
4460                --  In this case we need to construct a proper subtype of
4461                --  the parent type, in order to supply values to all the
4462                --  components. Otherwise there is one-one correspondence
4463                --  between the constraints and the stored discriminants.
4464
4465                First_Comp := Empty;
4466
4467                Discriminant := First_Stored_Discriminant (Base_Type (Typ));
4468
4469                while Present (Discriminant) loop
4470                   Num_Gird := Num_Gird + 1;
4471                   Next_Stored_Discriminant (Discriminant);
4472                end loop;
4473
4474                --  Case of more stored discriminants than new discriminants
4475
4476                if Num_Gird > Num_Disc then
4477
4478                   --  Create a proper subtype of the parent type, which is
4479                   --  the proper implementation type for the aggregate, and
4480                   --  convert it to the intended target type.
4481
4482                   Discriminant := First_Stored_Discriminant (Base_Type (Typ));
4483
4484                   while Present (Discriminant) loop
4485                      New_Comp :=
4486                        New_Copy_Tree (
4487                          Get_Discriminant_Value (
4488                              Discriminant,
4489                              Typ,
4490                              Discriminant_Constraint (Typ)));
4491                      Append (New_Comp, Constraints);
4492                      Next_Stored_Discriminant (Discriminant);
4493                   end loop;
4494
4495                   Decl :=
4496                     Make_Subtype_Declaration (Loc,
4497                       Defining_Identifier =>
4498                          Make_Defining_Identifier (Loc,
4499                             New_Internal_Name ('T')),
4500                       Subtype_Indication =>
4501                         Make_Subtype_Indication (Loc,
4502                           Subtype_Mark =>
4503                             New_Occurrence_Of (Etype (Base_Type (Typ)), Loc),
4504                           Constraint =>
4505                             Make_Index_Or_Discriminant_Constraint
4506                               (Loc, Constraints)));
4507
4508                   Insert_Action (N, Decl);
4509                   Prepend_Stored_Values (Base_Type (Typ));
4510
4511                   Set_Etype (N, Defining_Identifier (Decl));
4512                   Set_Analyzed (N);
4513
4514                   Rewrite (N, Unchecked_Convert_To (Typ, N));
4515                   Analyze (N);
4516
4517                --  Case where we do not have fewer new discriminants than
4518                --  stored discriminants, so in this case we can simply
4519                --  use the stored discriminants of the subtype.
4520
4521                else
4522                   Prepend_Stored_Values (Typ);
4523                end if;
4524             end Generate_Aggregate_For_Derived_Type;
4525          end if;
4526
4527          if Is_Tagged_Type (Typ) then
4528
4529             --  The tagged case, _parent and _tag component must be created.
4530
4531             --  Reset null_present unconditionally. tagged records always have
4532             --  at least one field (the tag or the parent)
4533
4534             Set_Null_Record_Present (N, False);
4535
4536             --  When the current aggregate comes from the expansion of an
4537             --  extension aggregate, the parent expr is replaced by an
4538             --  aggregate formed by selected components of this expr
4539
4540             if Present (Parent_Expr)
4541               and then Is_Empty_List (Comps)
4542             then
4543                Comp := First_Entity (Typ);
4544                while Present (Comp) loop
4545
4546                   --  Skip all entities that aren't discriminants or components
4547
4548                   if Ekind (Comp) /= E_Discriminant
4549                     and then Ekind (Comp) /= E_Component
4550                   then
4551                      null;
4552
4553                   --  Skip all expander-generated components
4554
4555                   elsif
4556                     not Comes_From_Source (Original_Record_Component (Comp))
4557                   then
4558                      null;
4559
4560                   else
4561                      New_Comp :=
4562                        Make_Selected_Component (Loc,
4563                          Prefix =>
4564                            Unchecked_Convert_To (Typ,
4565                              Duplicate_Subexpr (Parent_Expr, True)),
4566
4567                          Selector_Name => New_Occurrence_Of (Comp, Loc));
4568
4569                      Append_To (Comps,
4570                        Make_Component_Association (Loc,
4571                          Choices    =>
4572                            New_List (New_Occurrence_Of (Comp, Loc)),
4573                          Expression =>
4574                            New_Comp));
4575
4576                      Analyze_And_Resolve (New_Comp, Etype (Comp));
4577                   end if;
4578
4579                   Next_Entity (Comp);
4580                end loop;
4581             end if;
4582
4583             --  Compute the value for the Tag now, if the type is a root it
4584             --  will be included in the aggregate right away, otherwise it will
4585             --  be propagated to the parent aggregate
4586
4587             if Present (Orig_Tag) then
4588                Tag_Value := Orig_Tag;
4589             elsif Java_VM then
4590                Tag_Value := Empty;
4591             else
4592                Tag_Value := New_Occurrence_Of (Access_Disp_Table (Typ), Loc);
4593             end if;
4594
4595             --  For a derived type, an aggregate for the parent is formed with
4596             --  all the inherited components.
4597
4598             if Is_Derived_Type (Typ) then
4599
4600                declare
4601                   First_Comp   : Node_Id;
4602                   Parent_Comps : List_Id;
4603                   Parent_Aggr  : Node_Id;
4604                   Parent_Name  : Node_Id;
4605
4606                begin
4607                   --  Remove the inherited component association from the
4608                   --  aggregate and store them in the parent aggregate
4609
4610                   First_Comp := First (Component_Associations (N));
4611                   Parent_Comps := New_List;
4612
4613                   while Present (First_Comp)
4614                     and then Scope (Original_Record_Component (
4615                             Entity (First (Choices (First_Comp))))) /= Base_Typ
4616                   loop
4617                      Comp := First_Comp;
4618                      Next (First_Comp);
4619                      Remove (Comp);
4620                      Append (Comp, Parent_Comps);
4621                   end loop;
4622
4623                   Parent_Aggr := Make_Aggregate (Loc,
4624                     Component_Associations => Parent_Comps);
4625                   Set_Etype (Parent_Aggr, Etype (Base_Type (Typ)));
4626
4627                   --  Find the _parent component
4628
4629                   Comp := First_Component (Typ);
4630                   while Chars (Comp) /= Name_uParent loop
4631                      Comp := Next_Component (Comp);
4632                   end loop;
4633
4634                   Parent_Name := New_Occurrence_Of (Comp, Loc);
4635
4636                   --  Insert the parent aggregate
4637
4638                   Prepend_To (Component_Associations (N),
4639                     Make_Component_Association (Loc,
4640                       Choices    => New_List (Parent_Name),
4641                       Expression => Parent_Aggr));
4642
4643                   --  Expand recursively the parent propagating the right Tag
4644
4645                   Expand_Record_Aggregate (
4646                     Parent_Aggr, Tag_Value, Parent_Expr);
4647                end;
4648
4649             --  For a root type, the tag component is added (unless compiling
4650             --  for the Java VM, where tags are implicit).
4651
4652             elsif not Java_VM then
4653                declare
4654                   Tag_Name  : constant Node_Id :=
4655                                 New_Occurrence_Of (Tag_Component (Typ), Loc);
4656                   Typ_Tag   : constant Entity_Id := RTE (RE_Tag);
4657                   Conv_Node : constant Node_Id :=
4658                                 Unchecked_Convert_To (Typ_Tag, Tag_Value);
4659
4660                begin
4661                   Set_Etype (Conv_Node, Typ_Tag);
4662                   Prepend_To (Component_Associations (N),
4663                     Make_Component_Association (Loc,
4664                       Choices    => New_List (Tag_Name),
4665                       Expression => Conv_Node));
4666                end;
4667             end if;
4668          end if;
4669       end if;
4670    end Expand_Record_Aggregate;
4671
4672    ----------------------------
4673    -- Has_Default_Init_Comps --
4674    ----------------------------
4675
4676    function Has_Default_Init_Comps (N : Node_Id) return Boolean is
4677       Comps : constant List_Id := Component_Associations (N);
4678       C     : Node_Id;
4679       Expr  : Node_Id;
4680    begin
4681       pragma Assert (Nkind (N) = N_Aggregate
4682          or else Nkind (N) = N_Extension_Aggregate);
4683
4684       if No (Comps) then
4685          return False;
4686       end if;
4687
4688       --  Check if any direct component has default initialized components
4689
4690       C := First (Comps);
4691       while Present (C) loop
4692          if Box_Present (C) then
4693             return True;
4694          end if;
4695
4696          Next (C);
4697       end loop;
4698
4699       --  Recursive call in case of aggregate expression
4700
4701       C := First (Comps);
4702       while Present (C) loop
4703          Expr := Expression (C);
4704
4705          if Present (Expr)
4706            and then (Nkind (Expr) = N_Aggregate
4707                      or else Nkind (Expr) = N_Extension_Aggregate)
4708            and then Has_Default_Init_Comps (Expr)
4709          then
4710             return True;
4711          end if;
4712
4713          Next (C);
4714       end loop;
4715
4716       return False;
4717    end Has_Default_Init_Comps;
4718
4719    --------------------------
4720    -- Is_Delayed_Aggregate --
4721    --------------------------
4722
4723    function Is_Delayed_Aggregate (N : Node_Id) return Boolean is
4724       Node : Node_Id   := N;
4725       Kind : Node_Kind := Nkind (Node);
4726
4727    begin
4728       if Kind = N_Qualified_Expression then
4729          Node := Expression (Node);
4730          Kind := Nkind (Node);
4731       end if;
4732
4733       if Kind /= N_Aggregate and then Kind /= N_Extension_Aggregate then
4734          return False;
4735       else
4736          return Expansion_Delayed (Node);
4737       end if;
4738    end Is_Delayed_Aggregate;
4739
4740    --------------------
4741    -- Late_Expansion --
4742    --------------------
4743
4744    function Late_Expansion
4745      (N      : Node_Id;
4746       Typ    : Entity_Id;
4747       Target : Node_Id;
4748       Flist  : Node_Id   := Empty;
4749       Obj    : Entity_Id := Empty) return List_Id
4750    is
4751    begin
4752       if Is_Record_Type (Etype (N)) then
4753          return Build_Record_Aggr_Code (N, Typ, Target, Flist, Obj);
4754
4755       else pragma Assert (Is_Array_Type (Etype (N)));
4756          return
4757            Build_Array_Aggr_Code
4758              (N           => N,
4759               Ctype       => Component_Type (Etype (N)),
4760               Index       => First_Index (Typ),
4761               Into        => Target,
4762               Scalar_Comp => Is_Scalar_Type (Component_Type (Typ)),
4763               Indices     => No_List,
4764               Flist       => Flist);
4765       end if;
4766    end Late_Expansion;
4767
4768    ----------------------------------
4769    -- Make_OK_Assignment_Statement --
4770    ----------------------------------
4771
4772    function Make_OK_Assignment_Statement
4773      (Sloc       : Source_Ptr;
4774       Name       : Node_Id;
4775       Expression : Node_Id) return Node_Id
4776    is
4777    begin
4778       Set_Assignment_OK (Name);
4779       return Make_Assignment_Statement (Sloc, Name, Expression);
4780    end Make_OK_Assignment_Statement;
4781
4782    -----------------------
4783    -- Number_Of_Choices --
4784    -----------------------
4785
4786    function Number_Of_Choices (N : Node_Id) return Nat is
4787       Assoc  : Node_Id;
4788       Choice : Node_Id;
4789
4790       Nb_Choices : Nat := 0;
4791
4792    begin
4793       if Present (Expressions (N)) then
4794          return 0;
4795       end if;
4796
4797       Assoc := First (Component_Associations (N));
4798       while Present (Assoc) loop
4799
4800          Choice := First (Choices (Assoc));
4801          while Present (Choice) loop
4802
4803             if Nkind (Choice) /= N_Others_Choice then
4804                Nb_Choices := Nb_Choices + 1;
4805             end if;
4806
4807             Next (Choice);
4808          end loop;
4809
4810          Next (Assoc);
4811       end loop;
4812
4813       return Nb_Choices;
4814    end Number_Of_Choices;
4815
4816    ------------------------------------
4817    -- Packed_Array_Aggregate_Handled --
4818    ------------------------------------
4819
4820    --  The current version of this procedure will handle at compile time
4821    --  any array aggregate that meets these conditions:
4822
4823    --    One dimensional, bit packed
4824    --    Underlying packed type is modular type
4825    --    Bounds are within 32-bit Int range
4826    --    All bounds and values are static
4827
4828    function Packed_Array_Aggregate_Handled (N : Node_Id) return Boolean is
4829       Loc  : constant Source_Ptr := Sloc (N);
4830       Typ  : constant Entity_Id  := Etype (N);
4831       Ctyp : constant Entity_Id  := Component_Type (Typ);
4832
4833       Not_Handled : exception;
4834       --  Exception raised if this aggregate cannot be handled
4835
4836    begin
4837       --  For now, handle only one dimensional bit packed arrays
4838
4839       if not Is_Bit_Packed_Array (Typ)
4840         or else Number_Dimensions (Typ) > 1
4841         or else not Is_Modular_Integer_Type (Packed_Array_Type (Typ))
4842       then
4843          return False;
4844       end if;
4845
4846       declare
4847          Csiz  : constant Nat := UI_To_Int (Component_Size (Typ));
4848
4849          Lo : Node_Id;
4850          Hi : Node_Id;
4851          --  Bounds of index type
4852
4853          Lob : Uint;
4854          Hib : Uint;
4855          --  Values of bounds if compile time known
4856
4857          function Get_Component_Val (N : Node_Id) return Uint;
4858          --  Given a expression value N of the component type Ctyp, returns
4859          --  A value of Csiz (component size) bits representing this value.
4860          --  If the value is non-static or any other reason exists why the
4861          --  value cannot be returned, then Not_Handled is raised.
4862
4863          -----------------------
4864          -- Get_Component_Val --
4865          -----------------------
4866
4867          function Get_Component_Val (N : Node_Id) return Uint is
4868             Val  : Uint;
4869
4870          begin
4871             --  We have to analyze the expression here before doing any further
4872             --  processing here. The analysis of such expressions is deferred
4873             --  till expansion to prevent some problems of premature analysis.
4874
4875             Analyze_And_Resolve (N, Ctyp);
4876
4877             --  Must have a compile time value. String literals have to
4878             --  be converted into temporaries as well, because they cannot
4879             --  easily be converted into their bit representation.
4880
4881             if not Compile_Time_Known_Value (N)
4882               or else Nkind (N) = N_String_Literal
4883             then
4884                raise Not_Handled;
4885             end if;
4886
4887             Val := Expr_Rep_Value (N);
4888
4889             --  Adjust for bias, and strip proper number of bits
4890
4891             if Has_Biased_Representation (Ctyp) then
4892                Val := Val - Expr_Value (Type_Low_Bound (Ctyp));
4893             end if;
4894
4895             return Val mod Uint_2 ** Csiz;
4896          end Get_Component_Val;
4897
4898       --  Here we know we have a one dimensional bit packed array
4899
4900       begin
4901          Get_Index_Bounds (First_Index (Typ), Lo, Hi);
4902
4903          --  Cannot do anything if bounds are dynamic
4904
4905          if not Compile_Time_Known_Value (Lo)
4906               or else
4907             not Compile_Time_Known_Value (Hi)
4908          then
4909             return False;
4910          end if;
4911
4912          --  Or are silly out of range of int bounds
4913
4914          Lob := Expr_Value (Lo);
4915          Hib := Expr_Value (Hi);
4916
4917          if not UI_Is_In_Int_Range (Lob)
4918               or else
4919             not UI_Is_In_Int_Range (Hib)
4920          then
4921             return False;
4922          end if;
4923
4924          --  At this stage we have a suitable aggregate for handling
4925          --  at compile time (the only remaining checks, are that the
4926          --  values of expressions in the aggregate are compile time
4927          --  known (check performed by Get_Component_Val), and that
4928          --  any subtypes or ranges are statically known.
4929
4930          --  If the aggregate is not fully positional at this stage,
4931          --  then convert it to positional form. Either this will fail,
4932          --  in which case we can do nothing, or it will succeed, in
4933          --  which case we have succeeded in handling the aggregate,
4934          --  or it will stay an aggregate, in which case we have failed
4935          --  to handle this case.
4936
4937          if Present (Component_Associations (N)) then
4938             Convert_To_Positional
4939              (N, Max_Others_Replicate => 64, Handle_Bit_Packed => True);
4940             return Nkind (N) /= N_Aggregate;
4941          end if;
4942
4943          --  Otherwise we are all positional, so convert to proper value
4944
4945          declare
4946             Lov : constant Nat := UI_To_Int (Lob);
4947             Hiv : constant Nat := UI_To_Int (Hib);
4948
4949             Len : constant Nat := Int'Max (0, Hiv - Lov + 1);
4950             --  The length of the array (number of elements)
4951
4952             Aggregate_Val : Uint;
4953             --  Value of aggregate. The value is set in the low order
4954             --  bits of this value. For the little-endian case, the
4955             --  values are stored from low-order to high-order and
4956             --  for the big-endian case the values are stored from
4957             --  high-order to low-order. Note that gigi will take care
4958             --  of the conversions to left justify the value in the big
4959             --  endian case (because of left justified modular type
4960             --  processing), so we do not have to worry about that here.
4961
4962             Lit : Node_Id;
4963             --  Integer literal for resulting constructed value
4964
4965             Shift : Nat;
4966             --  Shift count from low order for next value
4967
4968             Incr : Int;
4969             --  Shift increment for loop
4970
4971             Expr : Node_Id;
4972             --  Next expression from positional parameters of aggregate
4973
4974          begin
4975             --  For little endian, we fill up the low order bits of the
4976             --  target value. For big endian we fill up the high order
4977             --  bits of the target value (which is a left justified
4978             --  modular value).
4979
4980             if Bytes_Big_Endian xor Debug_Flag_8 then
4981                Shift := Csiz * (Len - 1);
4982                Incr  := -Csiz;
4983             else
4984                Shift := 0;
4985                Incr  := +Csiz;
4986             end if;
4987
4988             --  Loop to set the values
4989
4990             if Len = 0 then
4991                Aggregate_Val := Uint_0;
4992             else
4993                Expr := First (Expressions (N));
4994                Aggregate_Val := Get_Component_Val (Expr) * Uint_2 ** Shift;
4995
4996                for J in 2 .. Len loop
4997                   Shift := Shift + Incr;
4998                   Next (Expr);
4999                   Aggregate_Val :=
5000                     Aggregate_Val + Get_Component_Val (Expr) * Uint_2 ** Shift;
5001                end loop;
5002             end if;
5003
5004             --  Now we can rewrite with the proper value
5005
5006             Lit :=
5007               Make_Integer_Literal (Loc,
5008                 Intval => Aggregate_Val);
5009             Set_Print_In_Hex (Lit);
5010
5011             --  Construct the expression using this literal. Note that it is
5012             --  important to qualify the literal with its proper modular type
5013             --  since universal integer does not have the required range and
5014             --  also this is a left justified modular type, which is important
5015             --  in the big-endian case.
5016
5017             Rewrite (N,
5018               Unchecked_Convert_To (Typ,
5019                 Make_Qualified_Expression (Loc,
5020                   Subtype_Mark =>
5021                     New_Occurrence_Of (Packed_Array_Type (Typ), Loc),
5022                   Expression   => Lit)));
5023
5024             Analyze_And_Resolve (N, Typ);
5025             return True;
5026          end;
5027       end;
5028
5029    exception
5030       when Not_Handled =>
5031          return False;
5032    end Packed_Array_Aggregate_Handled;
5033
5034    ----------------------------
5035    -- Has_Mutable_Components --
5036    ----------------------------
5037
5038    function Has_Mutable_Components (Typ : Entity_Id) return Boolean is
5039       Comp : Entity_Id;
5040
5041    begin
5042       Comp := First_Component (Typ);
5043
5044       while Present (Comp) loop
5045          if Is_Record_Type (Etype (Comp))
5046            and then Has_Discriminants (Etype (Comp))
5047            and then not Is_Constrained (Etype (Comp))
5048          then
5049             return True;
5050          end if;
5051
5052          Next_Component (Comp);
5053       end loop;
5054
5055       return False;
5056    end Has_Mutable_Components;
5057
5058    ------------------------------
5059    -- Initialize_Discriminants --
5060    ------------------------------
5061
5062    procedure Initialize_Discriminants (N : Node_Id; Typ : Entity_Id) is
5063       Loc  : constant Source_Ptr := Sloc (N);
5064       Bas  : constant Entity_Id  := Base_Type (Typ);
5065       Par  : constant Entity_Id  := Etype (Bas);
5066       Decl : constant Node_Id    := Parent (Par);
5067       Ref  : Node_Id;
5068
5069    begin
5070       if Is_Tagged_Type (Bas)
5071         and then Is_Derived_Type (Bas)
5072         and then Has_Discriminants (Par)
5073         and then Has_Discriminants (Bas)
5074         and then Number_Discriminants (Bas) /= Number_Discriminants (Par)
5075         and then Nkind (Decl) = N_Full_Type_Declaration
5076         and then Nkind (Type_Definition (Decl)) = N_Record_Definition
5077         and then Present
5078           (Variant_Part (Component_List (Type_Definition (Decl))))
5079         and then Nkind (N) /= N_Extension_Aggregate
5080       then
5081
5082          --   Call init proc to set discriminants.
5083          --   There should eventually be a special procedure for this ???
5084
5085          Ref := New_Reference_To (Defining_Identifier (N), Loc);
5086          Insert_Actions_After (N,
5087            Build_Initialization_Call (Sloc (N), Ref, Typ));
5088       end if;
5089    end Initialize_Discriminants;
5090
5091    ---------------------------
5092    -- Safe_Slice_Assignment --
5093    ---------------------------
5094
5095    function Safe_Slice_Assignment (N : Node_Id) return Boolean is
5096       Loc        : constant Source_Ptr := Sloc (Parent (N));
5097       Pref       : constant Node_Id    := Prefix (Name (Parent (N)));
5098       Range_Node : constant Node_Id    := Discrete_Range (Name (Parent (N)));
5099       Expr       : Node_Id;
5100       L_J        : Entity_Id;
5101       L_Iter     : Node_Id;
5102       L_Body     : Node_Id;
5103       Stat       : Node_Id;
5104
5105    begin
5106       --  Generate: for J in Range loop Pref (J) := Expr; end loop;
5107
5108       if Comes_From_Source (N)
5109         and then No (Expressions (N))
5110         and then Nkind (First (Choices (First (Component_Associations (N)))))
5111                    = N_Others_Choice
5112       then
5113          Expr :=
5114            Expression (First (Component_Associations (N)));
5115          L_J := Make_Defining_Identifier (Loc, New_Internal_Name ('J'));
5116
5117          L_Iter :=
5118            Make_Iteration_Scheme (Loc,
5119              Loop_Parameter_Specification =>
5120                Make_Loop_Parameter_Specification
5121                  (Loc,
5122                   Defining_Identifier         => L_J,
5123                   Discrete_Subtype_Definition => Relocate_Node (Range_Node)));
5124
5125          L_Body :=
5126            Make_Assignment_Statement (Loc,
5127               Name =>
5128                 Make_Indexed_Component (Loc,
5129                   Prefix      => Relocate_Node (Pref),
5130                   Expressions => New_List (New_Occurrence_Of (L_J, Loc))),
5131                Expression => Relocate_Node (Expr));
5132
5133          --  Construct the final loop
5134
5135          Stat :=
5136            Make_Implicit_Loop_Statement
5137              (Node             => Parent (N),
5138               Identifier       => Empty,
5139               Iteration_Scheme => L_Iter,
5140               Statements       => New_List (L_Body));
5141
5142          --  Set type of aggregate to be type of lhs in assignment,
5143          --  to suppress redundant length checks.
5144
5145          Set_Etype (N, Etype (Name (Parent (N))));
5146
5147          Rewrite (Parent (N), Stat);
5148          Analyze (Parent (N));
5149          return True;
5150
5151       else
5152          return False;
5153       end if;
5154    end Safe_Slice_Assignment;
5155
5156    ---------------------
5157    -- Sort_Case_Table --
5158    ---------------------
5159
5160    procedure Sort_Case_Table (Case_Table : in out Case_Table_Type) is
5161       L : constant Int := Case_Table'First;
5162       U : constant Int := Case_Table'Last;
5163       K : Int;
5164       J : Int;
5165       T : Case_Bounds;
5166
5167    begin
5168       K := L;
5169
5170       while K /= U loop
5171          T := Case_Table (K + 1);
5172          J := K + 1;
5173
5174          while J /= L
5175            and then Expr_Value (Case_Table (J - 1).Choice_Lo) >
5176                     Expr_Value (T.Choice_Lo)
5177          loop
5178             Case_Table (J) := Case_Table (J - 1);
5179             J := J - 1;
5180          end loop;
5181
5182          Case_Table (J) := T;
5183          K := K + 1;
5184       end loop;
5185    end Sort_Case_Table;
5186
5187 end Exp_Aggr;