OSDN Git Service

Patch to fix -mcpu=G5 interface to EH runtime library.
[pf3gnuchains/gcc-fork.git] / gcc / ada / exp_aggr.adb
index e32fe91..7bc0a76 100644 (file)
@@ -6,9 +6,7 @@
 --                                                                          --
 --                                 B o d y                                  --
 --                                                                          --
---                            $Revision$
---                                                                          --
---          Copyright (C) 1992-2001 Free Software Foundation, Inc.          --
+--          Copyright (C) 1992-2004 Free Software Foundation, Inc.          --
 --                                                                          --
 -- GNAT is free software;  you can  redistribute it  and/or modify it under --
 -- terms of the  GNU General Public License as published  by the Free Soft- --
 -- MA 02111-1307, USA.                                                      --
 --                                                                          --
 -- GNAT was originally developed  by the GNAT team at  New York University. --
--- It is now maintained by Ada Core Technologies Inc (http://www.gnat.com). --
+-- Extensive contributions were provided by Ada Core Technologies Inc.      --
 --                                                                          --
 ------------------------------------------------------------------------------
 
 with Atree;    use Atree;
 with Checks;   use Checks;
+with Debug;    use Debug;
 with Einfo;    use Einfo;
 with Elists;   use Elists;
 with Expander; use Expander;
 with Exp_Util; use Exp_Util;
 with Exp_Ch3;  use Exp_Ch3;
 with Exp_Ch7;  use Exp_Ch7;
+with Exp_Ch9;  use Exp_Ch9;
+with Exp_Tss;  use Exp_Tss;
 with Freeze;   use Freeze;
 with Hostparm; use Hostparm;
 with Itypes;   use Itypes;
+with Lib;      use Lib;
 with Nmake;    use Nmake;
 with Nlists;   use Nlists;
 with Restrict; use Restrict;
+with Rident;   use Rident;
 with Rtsfind;  use Rtsfind;
+with Ttypes;   use Ttypes;
 with Sem;      use Sem;
 with Sem_Ch3;  use Sem_Ch3;
 with Sem_Eval; use Sem_Eval;
@@ -69,6 +73,10 @@ package body Exp_Aggr is
    --  statement of variant part will usually be small and probably in near
    --  sorted order.
 
+   function Has_Default_Init_Comps (N : Node_Id) return Boolean;
+   --  N is an aggregate (record or array). Checks the presence of default
+   --  initialization (<>) in any component (Ada 2005: AI-287)
+
    ------------------------------------------------------
    -- Local subprograms for Record Aggregate Expansion --
    ------------------------------------------------------
@@ -96,12 +104,12 @@ package body Exp_Aggr is
    --  assignments component per component.
 
    function Build_Record_Aggr_Code
-     (N      : Node_Id;
-      Typ    : Entity_Id;
-      Target : Node_Id;
-      Flist  : Node_Id   := Empty;
-      Obj    : Entity_Id := Empty)
-      return   List_Id;
+     (N                             : Node_Id;
+      Typ                           : Entity_Id;
+      Target                        : Node_Id;
+      Flist                         : Node_Id   := Empty;
+      Obj                           : Entity_Id := Empty;
+      Is_Limited_Ancestor_Expansion : Boolean   := False) return List_Id;
    --  N is an N_Aggregate or a N_Extension_Aggregate. Typ is the type
    --  of the aggregate. Target is an expression containing the
    --  location on which the component by component assignments will
@@ -112,11 +120,49 @@ package body Exp_Aggr is
    --  object declaration and dynamic allocation cases, it contains
    --  an entity that allows to know if the value being created needs to be
    --  attached to the final list in case of pragma finalize_Storage_Only.
+   --  Is_Limited_Ancestor_Expansion indicates that the function has been
+   --  called recursively to expand the limited ancestor to avoid copying it.
+
+   function Has_Mutable_Components (Typ : Entity_Id) return Boolean;
+   --  Return true if one of the component is of a discriminated type with
+   --  defaults. An aggregate for a type with mutable components must be
+   --  expanded into individual assignments.
+
+   procedure Initialize_Discriminants (N : Node_Id; Typ : Entity_Id);
+   --  If the type of the aggregate is a type extension with renamed discrimi-
+   --  nants, we must initialize the hidden discriminants of the parent.
+   --  Otherwise, the target object must not be initialized. The discriminants
+   --  are initialized by calling the initialization procedure for the type.
+   --  This is incorrect if the initialization of other components has any
+   --  side effects. We restrict this call to the case where the parent type
+   --  has a variant part, because this is the only case where the hidden
+   --  discriminants are accessed, namely when calling discriminant checking
+   --  functions of the parent type, and when applying a stream attribute to
+   --  an object of the derived type.
 
    -----------------------------------------------------
-   -- Local subprograms for array aggregate expansion --
+   -- Local Subprograms for Array Aggregate Expansion --
    -----------------------------------------------------
 
+   procedure Convert_To_Positional
+     (N                    : Node_Id;
+      Max_Others_Replicate : Nat     := 5;
+      Handle_Bit_Packed    : Boolean := False);
+   --  If possible, convert named notation to positional notation. This
+   --  conversion is possible only in some static cases. If the conversion
+   --  is possible, then N is rewritten with the analyzed converted
+   --  aggregate. The parameter Max_Others_Replicate controls the maximum
+   --  number of values corresponding to an others choice that will be
+   --  converted to positional notation (the default of 5 is the normal
+   --  limit, and reflects the fact that normally the loop is better than
+   --  a lot of separate assignments). Note that this limit gets overridden
+   --  in any case if either of the restrictions No_Elaboration_Code or
+   --  No_Implicit_Loops is set. The parameter Handle_Bit_Packed is usually
+   --  set False (since we do not expect the back end to handle bit packed
+   --  arrays, so the normal case of conversion is pointless), but in the
+   --  special case of a call from Packed_Array_Aggregate_Handled, we set
+   --  this parameter to True, since these are cases we handle in there.
+
    procedure Expand_Array_Aggregate (N : Node_Id);
    --  This is the top-level routine to perform array aggregate expansion.
    --  N is the N_Aggregate node to be expanded.
@@ -127,21 +173,24 @@ package body Exp_Aggr is
 
    function Build_Array_Aggr_Code
      (N           : Node_Id;
+      Ctype       : Entity_Id;
       Index       : Node_Id;
       Into        : Node_Id;
       Scalar_Comp : Boolean;
       Indices     : List_Id := No_List;
-      Flist       : Node_Id := Empty)
-      return        List_Id;
+      Flist       : Node_Id := Empty) return List_Id;
    --  This recursive routine returns a list of statements containing the
    --  loops and assignments that are needed for the expansion of the array
    --  aggregate N.
    --
-   --    N is the (sub-)aggregate node to be expanded into code.
+   --    N is the (sub-)aggregate node to be expanded into code. This node
+   --    has been fully analyzed, and its Etype is properly set.
    --
    --    Index is the index node corresponding to the array sub-aggregate N.
    --
    --    Into is the target expression into which we are copying the aggregate.
+   --    Note that this node may not have been analyzed yet, and so the Etype
+   --    field may not be set.
    --
    --    Scalar_Comp is True if the component type of the aggregate is scalar.
    --
@@ -160,8 +209,7 @@ package body Exp_Aggr is
       Typ    : Entity_Id;
       Target : Node_Id;
       Flist  : Node_Id := Empty;
-      Obj    : Entity_Id := Empty)
-      return List_Id;
+      Obj    : Entity_Id := Empty) return List_Id;
    --  N is a nested (record or array) aggregate that has been marked
    --  with 'Delay_Expansion'. Typ is the expected type of the
    --  aggregate and Target is a (duplicable) expression that will
@@ -178,17 +226,22 @@ package body Exp_Aggr is
    function Make_OK_Assignment_Statement
      (Sloc       : Source_Ptr;
       Name       : Node_Id;
-      Expression : Node_Id)
-      return       Node_Id;
+      Expression : Node_Id) return Node_Id;
    --  This is like Make_Assignment_Statement, except that Assignment_OK
    --  is set in the left operand. All assignments built by this unit
    --  use this routine. This is needed to deal with assignments to
    --  initialized constants that are done in place.
 
-   function Safe_Slice_Assignment
-     (N    : Node_Id;
-      Typ  : Entity_Id)
-      return Boolean;
+   function Packed_Array_Aggregate_Handled (N : Node_Id) return Boolean;
+   --  Given an array aggregate, this function handles the case of a packed
+   --  array aggregate with all constant values, where the aggregate can be
+   --  evaluated at compile time. If this is possible, then N is rewritten
+   --  to be its proper compile time value with all the components properly
+   --  assembled. The expression is analyzed and resolved and True is
+   --  returned. If this transformation is not possible, N is unchanged
+   --  and False is returned
+
+   function Safe_Slice_Assignment (N : Node_Id) return Boolean;
    --  If a slice assignment has an aggregate with a single others_choice,
    --  the assignment can be done in place even if bounds are not static,
    --  by converting it into a loop over the discrete range of the slice.
@@ -213,6 +266,8 @@ package body Exp_Aggr is
    --    5. The array component type is tagged, which may necessitate
    --       reassignment of proper tags.
 
+   --    6. The array component type might have unaligned bit components
+
    function Backend_Processing_Possible (N : Node_Id) return Boolean is
       Typ : constant Entity_Id := Etype (N);
       --  Typ is the correct constrained array subtype of the aggregate.
@@ -266,7 +321,7 @@ package body Exp_Aggr is
          return False;
       end if;
 
-      --  Checks 4  (array must not be multi-dimensional Fortran case)
+      --  Checks 4 (array must not be multi-dimensional Fortran case)
 
       if Convention (Typ) = Convention_Fortran
         and then Number_Dimensions (Typ) > 1
@@ -299,6 +354,12 @@ package body Exp_Aggr is
          return False;
       end if;
 
+      --  Checks 6 (component type must not have bit aligned components)
+
+      if Type_May_Have_Bit_Aligned_Components (Component_Type (Typ)) then
+         return False;
+      end if;
+
       --  Backend processing is possible
 
       Set_Compile_Time_Known_Aggregate (N, True);
@@ -340,20 +401,20 @@ package body Exp_Aggr is
 
    --         we always generate something like:
 
-   --             I : Index_Type := Index_Of_Last_Positional_Element;
-   --             while I < H loop
-   --                I := Index_Base'Succ (I)
-   --                Tmp (I) := E;
+   --             J : Index_Type := Index_Of_Last_Positional_Element;
+   --             while J < H loop
+   --                J := Index_Base'Succ (J)
+   --                Tmp (J) := E;
    --             end loop;
 
    function Build_Array_Aggr_Code
      (N           : Node_Id;
+      Ctype       : Entity_Id;
       Index       : Node_Id;
       Into        : Node_Id;
       Scalar_Comp : Boolean;
       Indices     : List_Id := No_List;
-      Flist       : Node_Id := Empty)
-      return        List_Id
+      Flist       : Node_Id := Empty) return List_Id
    is
       Loc          : constant Source_Ptr := Sloc (N);
       Index_Base   : constant Entity_Id  := Base_Type (Etype (Index));
@@ -375,13 +436,16 @@ package body Exp_Aggr is
       --  Returns a new reference to the index type name.
 
       function Gen_Assign (Ind : Node_Id; Expr : Node_Id) return List_Id;
-      --  Ind must be a side-effect free expression.
-      --  If the input aggregate N to Build_Loop contains no sub-aggregates,
-      --  This routine returns the assignment statement
+      --  Ind must be a side-effect free expression. If the input aggregate
+      --  N to Build_Loop contains no sub-aggregates, then this function
+      --  returns the assignment statement:
       --
       --     Into (Indices, Ind) := Expr;
       --
       --  Otherwise we call Build_Code recursively.
+      --
+      --  Ada 2005 (AI-287): In case of default initialized component, Expr
+      --  is empty and we generate a call to the corresponding IP subprogram.
 
       function Gen_Loop (L, H : Node_Id; Expr : Node_Id) return List_Id;
       --  Nodes L and H must be side-effect free expressions.
@@ -401,13 +465,13 @@ package body Exp_Aggr is
       --  If the input aggregate N to Build_Loop contains no sub-aggregates,
       --  This routine returns the while loop statement
       --
-      --     I : Index_Base := L;
-      --     while I < H loop
-      --        I := Index_Base'Succ (I);
-      --        Into (Indices, I) := Expr;
+      --     J : Index_Base := L;
+      --     while J < H loop
+      --        J := Index_Base'Succ (J);
+      --        Into (Indices, J) := Expr;
       --     end loop;
       --
-      --  Otherwise we call Build_Code recursively.
+      --  Otherwise we call Build_Code recursively
 
       function Local_Compile_Time_Known_Value (E : Node_Id) return Boolean;
       function Local_Expr_Value               (E : Node_Id) return Uint;
@@ -427,9 +491,8 @@ package body Exp_Aggr is
          Expr_Pos : Node_Id;
          Expr     : Node_Id;
          To_Pos   : Node_Id;
-
-         U_To  : Uint;
-         U_Val : Uint := UI_From_Int (Val);
+         U_To     : Uint;
+         U_Val    : constant Uint := UI_From_Int (Val);
 
       begin
          --  Note: do not try to optimize the case of Val = 0, because
@@ -587,7 +650,7 @@ package body Exp_Aggr is
       ----------------
 
       function Gen_Assign (Ind : Node_Id; Expr : Node_Id) return List_Id is
-         L : List_Id := New_List;
+         L : constant List_Id := New_List;
          F : Entity_Id;
          A : Node_Id;
 
@@ -609,7 +672,13 @@ package body Exp_Aggr is
             Res : List_Id;
 
          begin
-            if Nkind (Parent (Expr)) = N_Component_Association
+            --  Ada 2005 (AI-287): Do nothing else in case of default
+            --  initialized component.
+
+            if not Present (Expr) then
+               return Lis;
+
+            elsif Nkind (Parent (Expr)) = N_Component_Association
               and then Present (Loop_Actions (Parent (Expr)))
             then
                Append_List (Lis, Loop_Actions (Parent (Expr)));
@@ -641,32 +710,42 @@ package body Exp_Aggr is
               and then Present (Scope (Entity (Into)))
             then
                F := Find_Final_List (Scope (Entity (Into)));
-
             else
                F := Find_Final_List (Current_Scope);
             end if;
          else
-            F := 0;
+            F := Empty;
          end if;
 
          if Present (Next_Index (Index)) then
             return
               Add_Loop_Actions (
                 Build_Array_Aggr_Code
-                  (Expr, Next_Index (Index),
-                    Into, Scalar_Comp, New_Indices, F));
+                  (N           => Expr,
+                   Ctype       => Ctype,
+                   Index       => Next_Index (Index),
+                   Into        => Into,
+                   Scalar_Comp => Scalar_Comp,
+                   Indices     => New_Indices,
+                   Flist       => F));
          end if;
 
          --  If we get here then we are at a bottom-level (sub-)aggregate
 
-         Indexed_Comp :=  Checks_Off (
-             Make_Indexed_Component (Loc,
-               Prefix      => New_Copy_Tree (Into),
-               Expressions => New_Indices));
+         Indexed_Comp :=
+           Checks_Off
+             (Make_Indexed_Component (Loc,
+                Prefix      => New_Copy_Tree (Into),
+                Expressions => New_Indices));
 
          Set_Assignment_OK (Indexed_Comp);
 
-         if Nkind (Expr) = N_Qualified_Expression then
+         --  Ada 2005 (AI-287): In case of default initialized component, Expr
+         --  is not present (and therefore we also initialize Expr_Q to empty).
+
+         if not Present (Expr) then
+            Expr_Q := Empty;
+         elsif Nkind (Expr) = N_Qualified_Expression then
             Expr_Q := Expression (Expr);
          else
             Expr_Q := Expr;
@@ -676,41 +755,56 @@ package body Exp_Aggr is
            and then Etype (N) /= Any_Composite
          then
             Comp_Type := Component_Type (Etype (N));
+            pragma Assert (Comp_Type = Ctype); --  AI-287
 
          elsif Present (Next (First (New_Indices))) then
 
-            --  this is a multidimensional array. Recover the component
-            --  type from the outermost aggregate, because subaggregates
-            --  do not have an assigned type.
+            --  Ada 2005 (AI-287): Do nothing in case of default initialized
+            --  component because we have received the component type in
+            --  the formal parameter Ctype.
 
-            declare
-               P : Node_Id := Parent (Expr);
+            --  ??? Some assert pragmas have been added to check if this new
+            --      formal can be used to replace this code in all cases.
 
-            begin
-               while Present (P) loop
+            if Present (Expr) then
 
-                  if Nkind (P) = N_Aggregate
-                    and then Present (Etype (P))
-                  then
-                     Comp_Type := Component_Type (Etype (P));
-                     exit;
+               --  This is a multidimensional array. Recover the component
+               --  type from the outermost aggregate, because subaggregates
+               --  do not have an assigned type.
 
-                  else
-                     P := Parent (P);
-                  end if;
-               end loop;
-            end;
+               declare
+                  P : Node_Id := Parent (Expr);
+
+               begin
+                  while Present (P) loop
+                     if Nkind (P) = N_Aggregate
+                       and then Present (Etype (P))
+                     then
+                        Comp_Type := Component_Type (Etype (P));
+                        exit;
+
+                     else
+                        P := Parent (P);
+                     end if;
+                  end loop;
+
+                  pragma Assert (Comp_Type = Ctype); --  AI-287
+               end;
+            end if;
          end if;
 
-         if (Nkind (Expr_Q) = N_Aggregate
-           or else Nkind (Expr_Q) = N_Extension_Aggregate)
-         then
+         --  Ada 2005 (AI-287): We only analyze the expression in case of non-
+         --  default initialized components (otherwise Expr_Q is not present).
 
+         if Present (Expr_Q)
+           and then (Nkind (Expr_Q) = N_Aggregate
+                     or else Nkind (Expr_Q) = N_Extension_Aggregate)
+         then
             --  At this stage the Expression may not have been
             --  analyzed yet because the array aggregate code has not
             --  been updated to use the Expansion_Delayed flag and
             --  avoid analysis altogether to solve the same problem
-            --  (see Resolve_Aggr_Expr) so let's do the analysis of
+            --  (see Resolve_Aggr_Expr). So let us do the analysis of
             --  non-array aggregates now in order to get the value of
             --  Expansion_Delayed flag for the inner aggregate ???
 
@@ -725,59 +819,76 @@ package body Exp_Aggr is
             end if;
          end if;
 
-         --  Now generate the assignment with no associated controlled
-         --  actions since the target of the assignment may not have
-         --  been initialized, it is not possible to Finalize it as
-         --  expected by normal controlled assignment. The rest of the
-         --  controlled actions are done manually with the proper
-         --  finalization list coming from the context.
-
-         A :=
-           Make_OK_Assignment_Statement (Loc,
-             Name       => Indexed_Comp,
-             Expression => New_Copy_Tree (Expr));
+         --  Ada 2005 (AI-287): In case of default initialized component, call
+         --  the initialization subprogram associated with the component type.
 
-         if Present (Comp_Type) and then Controlled_Type (Comp_Type) then
-            Set_No_Ctrl_Actions (A);
-         end if;
+         if not Present (Expr) then
 
-         Append_To (L, A);
+            if Present (Base_Init_Proc (Etype (Ctype)))
+              or else Has_Task (Base_Type (Ctype))
+            then
+               Append_List_To (L,
+                 Build_Initialization_Call (Loc,
+                   Id_Ref            => Indexed_Comp,
+                   Typ               => Ctype,
+                   With_Default_Init => True));
+            end if;
 
-         --  Adjust the tag if tagged (because of possible view
-         --  conversions), unless compiling for the Java VM
-         --  where tags are implicit.
+         else
+            --  Now generate the assignment with no associated controlled
+            --  actions since the target of the assignment may not have
+            --  been initialized, it is not possible to Finalize it as
+            --  expected by normal controlled assignment. The rest of the
+            --  controlled actions are done manually with the proper
+            --  finalization list coming from the context.
 
-         if Present (Comp_Type)
-           and then Is_Tagged_Type (Comp_Type)
-           and then not Java_VM
-         then
             A :=
               Make_OK_Assignment_Statement (Loc,
-                Name =>
-                  Make_Selected_Component (Loc,
-                    Prefix =>  New_Copy_Tree (Indexed_Comp),
-                    Selector_Name =>
-                      New_Reference_To (Tag_Component (Comp_Type), Loc)),
+                Name       => Indexed_Comp,
+                Expression => New_Copy_Tree (Expr));
 
-                Expression =>
-                  Unchecked_Convert_To (RTE (RE_Tag),
-                    New_Reference_To (
-                      Access_Disp_Table (Comp_Type), Loc)));
+            if Present (Comp_Type) and then Controlled_Type (Comp_Type) then
+               Set_No_Ctrl_Actions (A);
+            end if;
 
             Append_To (L, A);
-         end if;
 
-         --  Adjust and Attach the component to the proper final list
-         --  which can be the controller of the outer record object or
-         --  the final list associated with the scope
+            --  Adjust the tag if tagged (because of possible view
+            --  conversions), unless compiling for the Java VM
+            --  where tags are implicit.
 
-         if Present (Comp_Type)  and then Controlled_Type (Comp_Type) then
-            Append_List_To (L,
-              Make_Adjust_Call (
-                Ref         => New_Copy_Tree (Indexed_Comp),
-                Typ         => Comp_Type,
-                Flist_Ref   => F,
-                With_Attach => Make_Integer_Literal (Loc, 1)));
+            if Present (Comp_Type)
+              and then Is_Tagged_Type (Comp_Type)
+              and then not Java_VM
+            then
+               A :=
+                 Make_OK_Assignment_Statement (Loc,
+                   Name =>
+                     Make_Selected_Component (Loc,
+                       Prefix =>  New_Copy_Tree (Indexed_Comp),
+                       Selector_Name =>
+                         New_Reference_To (Tag_Component (Comp_Type), Loc)),
+
+                   Expression =>
+                     Unchecked_Convert_To (RTE (RE_Tag),
+                       New_Reference_To (
+                         Access_Disp_Table (Comp_Type), Loc)));
+
+               Append_To (L, A);
+            end if;
+
+            --  Adjust and Attach the component to the proper final list
+            --  which can be the controller of the outer record object or
+            --  the final list associated with the scope
+
+            if Present (Comp_Type)  and then Controlled_Type (Comp_Type) then
+               Append_List_To (L,
+                 Make_Adjust_Call (
+                   Ref         => New_Copy_Tree (Indexed_Comp),
+                   Typ         => Comp_Type,
+                   Flist_Ref   => F,
+                   With_Attach => Make_Integer_Literal (Loc, 1)));
+            end if;
          end if;
 
          return Add_Loop_Actions (L);
@@ -788,19 +899,19 @@ package body Exp_Aggr is
       --------------
 
       function Gen_Loop (L, H : Node_Id; Expr : Node_Id) return List_Id is
-         L_I : Node_Id;
+         L_J : Node_Id;
 
          L_Range : Node_Id;
          --  Index_Base'(L) .. Index_Base'(H)
 
          L_Iteration_Scheme : Node_Id;
-         --  L_I in Index_Base'(L) .. Index_Base'(H)
+         --  L_J in Index_Base'(L) .. Index_Base'(H)
 
          L_Body : List_Id;
          --  The statements to execute in the loop
 
-         S : List_Id := New_List;
-         --  list of statement
+         S : constant List_Id := New_List;
+         --  List of statements
 
          Tcopy : Node_Id;
          --  Copy of expression tree, used for checking purposes
@@ -811,21 +922,29 @@ package body Exp_Aggr is
          if Empty_Range (L, H) then
             Append_To (S, Make_Null_Statement (Loc));
 
-            --  The expression must be type-checked even though no component
-            --  of the aggregate will have this value. This is done only for
-            --  actual components of the array, not for subaggregates. Do the
-            --  check on a copy, because the expression may be shared among
-            --  several choices, some of which might be non-null.
+            --  Ada 2005 (AI-287): Nothing else need to be done in case of
+            --  default initialized component.
 
-            if Present (Etype (N))
-              and then Is_Array_Type (Etype (N))
-              and then No (Next_Index (Index))
-            then
-               Expander_Mode_Save_And_Set (False);
-               Tcopy := New_Copy_Tree (Expr);
-               Set_Parent (Tcopy, N);
-               Analyze_And_Resolve (Tcopy, Component_Type (Etype (N)));
-               Expander_Mode_Restore;
+            if not Present (Expr) then
+               null;
+
+            else
+               --  The expression must be type-checked even though no component
+               --  of the aggregate will have this value. This is done only for
+               --  actual components of the array, not for subaggregates. Do
+               --  the check on a copy, because the expression may be shared
+               --  among several choices, some of which might be non-null.
+
+               if Present (Etype (N))
+                 and then Is_Array_Type (Etype (N))
+                 and then No (Next_Index (Index))
+               then
+                  Expander_Mode_Save_And_Set (False);
+                  Tcopy := New_Copy_Tree (Expr);
+                  Set_Parent (Tcopy, N);
+                  Analyze_And_Resolve (Tcopy, Component_Type (Etype (N)));
+                  Expander_Mode_Restore;
+               end if;
             end if;
 
             return S;
@@ -845,6 +964,7 @@ package body Exp_Aggr is
            and then Local_Compile_Time_Known_Value (H)
            and then Local_Expr_Value (H) - Local_Expr_Value (L) <= 2
          then
+
             Append_List_To (S, Gen_Assign (New_Copy_Tree (L), Expr));
             Append_List_To (S, Gen_Assign (Add (1, To => L), Expr));
 
@@ -855,9 +975,9 @@ package body Exp_Aggr is
             return S;
          end if;
 
-         --  Otherwise construct the loop, starting with the loop index L_I
+         --  Otherwise construct the loop, starting with the loop index L_J
 
-         L_I := Make_Defining_Identifier (Loc, New_Internal_Name ('I'));
+         L_J := Make_Defining_Identifier (Loc, New_Internal_Name ('J'));
 
          --  Construct "L .. H"
 
@@ -873,7 +993,7 @@ package body Exp_Aggr is
                                Subtype_Mark => Index_Base_Name,
                                Expression => H));
 
-         --  Construct "for L_I in Index_Base range L .. H"
+         --  Construct "for L_J in Index_Base range L .. H"
 
          L_Iteration_Scheme :=
            Make_Iteration_Scheme
@@ -881,12 +1001,12 @@ package body Exp_Aggr is
               Loop_Parameter_Specification =>
                 Make_Loop_Parameter_Specification
                   (Loc,
-                   Defining_Identifier         => L_I,
+                   Defining_Identifier         => L_J,
                    Discrete_Subtype_Definition => L_Range));
 
          --  Construct the statements to execute in the loop body
 
-         L_Body := Gen_Assign (New_Reference_To (L_I, Loc), Expr);
+         L_Body := Gen_Assign (New_Reference_To (L_J, Loc), Expr);
 
          --  Construct the final loop
 
@@ -905,32 +1025,31 @@ package body Exp_Aggr is
 
       --  The code built is
 
-      --     W_I : Index_Base := L;
-      --     while W_I < H loop
-      --        W_I := Index_Base'Succ (W);
+      --     W_J : Index_Base := L;
+      --     while W_J < H loop
+      --        W_J := Index_Base'Succ (W);
       --        L_Body;
       --     end loop;
 
       function Gen_While (L, H : Node_Id; Expr : Node_Id) return List_Id is
-
-         W_I : Node_Id;
+         W_J : Node_Id;
 
          W_Decl : Node_Id;
-         --  W_I : Base_Type := L;
+         --  W_J : Base_Type := L;
 
          W_Iteration_Scheme : Node_Id;
-         --  while W_I < H
+         --  while W_J < H
 
          W_Index_Succ : Node_Id;
-         --  Index_Base'Succ (I)
+         --  Index_Base'Succ (J)
 
-         W_Increment  : Node_Id;
-         --  W_I := Index_Base'Succ (W)
+         W_Increment : Node_Id;
+         --  W_J := Index_Base'Succ (W)
 
-         W_Body : List_Id := New_List;
+         W_Body : constant List_Id := New_List;
          --  The statements to execute in the loop
 
-         S : List_Id := New_List;
+         S : constant List_Id := New_List;
          --  list of statement
 
       begin
@@ -941,13 +1060,13 @@ package body Exp_Aggr is
             return S;
          end if;
 
-         --  Build the decl of W_I
+         --  Build the decl of W_J
 
-         W_I    := Make_Defining_Identifier (Loc, New_Internal_Name ('I'));
+         W_J    := Make_Defining_Identifier (Loc, New_Internal_Name ('J'));
          W_Decl :=
            Make_Object_Declaration
              (Loc,
-              Defining_Identifier => W_I,
+              Defining_Identifier => W_J,
               Object_Definition   => Index_Base_Name,
               Expression          => L);
 
@@ -957,14 +1076,14 @@ package body Exp_Aggr is
 
          Append_To (S, W_Decl);
 
-         --  construct " while W_I < H"
+         --  Construct " while W_J < H"
 
          W_Iteration_Scheme :=
            Make_Iteration_Scheme
              (Loc,
               Condition => Make_Op_Lt
                              (Loc,
-                              Left_Opnd  => New_Reference_To (W_I, Loc),
+                              Left_Opnd  => New_Reference_To (W_J, Loc),
                               Right_Opnd => New_Copy_Tree (H)));
 
          --  Construct the statements to execute in the loop body
@@ -974,17 +1093,17 @@ package body Exp_Aggr is
              (Loc,
               Prefix         => Index_Base_Name,
               Attribute_Name => Name_Succ,
-              Expressions    => New_List (New_Reference_To (W_I, Loc)));
+              Expressions    => New_List (New_Reference_To (W_J, Loc)));
 
          W_Increment  :=
            Make_OK_Assignment_Statement
              (Loc,
-              Name       => New_Reference_To (W_I, Loc),
+              Name       => New_Reference_To (W_J, Loc),
               Expression => W_Index_Succ);
 
          Append_To (W_Body, W_Increment);
          Append_List_To (W_Body,
-           Gen_Assign (New_Reference_To (W_I, Loc), Expr));
+           Gen_Assign (New_Reference_To (W_J, Loc), Expr));
 
          --  Construct the final loop
 
@@ -1015,8 +1134,8 @@ package body Exp_Aggr is
          return Compile_Time_Known_Value (E)
            or else
              (Nkind (E) = N_Attribute_Reference
-              and then Attribute_Name (E) = Name_Val
-              and then Compile_Time_Known_Value (First (Expressions (E))));
+               and then Attribute_Name (E) = Name_Val
+               and then Compile_Time_Known_Value (First (Expressions (E))));
       end Local_Compile_Time_Known_Value;
 
       ----------------------
@@ -1037,8 +1156,10 @@ package body Exp_Aggr is
       Assoc  : Node_Id;
       Choice : Node_Id;
       Expr   : Node_Id;
+      Typ    : Entity_Id;
 
-      Others_Expr : Node_Id   := Empty;
+      Others_Expr         : Node_Id := Empty;
+      Others_Mbox_Present : Boolean := False;
 
       Aggr_L : constant Node_Id := Low_Bound (Aggregate_Bounds (N));
       Aggr_H : constant Node_Id := High_Bound (Aggregate_Bounds (N));
@@ -1046,12 +1167,12 @@ package body Exp_Aggr is
       --  the code generated by Build_Array_Aggr_Code is executed then these
       --  bounds are OK. Otherwise a Constraint_Error would have been raised.
 
-      Aggr_Low  : constant Node_Id := Duplicate_Subexpr (Aggr_L);
-      Aggr_High : constant Node_Id := Duplicate_Subexpr (Aggr_H);
-      --  After Duplicate_Subexpr these are side-effect free.
+      Aggr_Low  : constant Node_Id := Duplicate_Subexpr_No_Checks (Aggr_L);
+      Aggr_High : constant Node_Id := Duplicate_Subexpr_No_Checks (Aggr_H);
+      --  After Duplicate_Subexpr these are side-effect free
 
-      Low  : Node_Id;
-      High : Node_Id;
+      Low        : Node_Id;
+      High       : Node_Id;
 
       Nb_Choices : Nat := 0;
       Table      : Case_Table_Type (1 .. Number_Of_Choices (N));
@@ -1060,12 +1181,33 @@ package body Exp_Aggr is
       Nb_Elements : Int;
       --  Number of elements in the positional aggregate
 
-      New_Code : List_Id := New_List;
+      New_Code : constant List_Id := New_List;
 
    --  Start of processing for Build_Array_Aggr_Code
 
    begin
+      --  First before we start, a special case. if we have a bit packed
+      --  array represented as a modular type, then clear the value to
+      --  zero first, to ensure that unused bits are properly cleared.
+
+      Typ := Etype (N);
+
+      if Present (Typ)
+        and then Is_Bit_Packed_Array (Typ)
+        and then Is_Modular_Integer_Type (Packed_Array_Type (Typ))
+      then
+         Append_To (New_Code,
+           Make_Assignment_Statement (Loc,
+             Name => New_Copy_Tree (Into),
+             Expression =>
+               Unchecked_Convert_To (Typ,
+                 Make_Integer_Literal (Loc, Uint_0))));
+      end if;
+
+      --  We can skip this
       --  STEP 1: Process component associations
+      --  For those associations that may generate a loop, initialize
+      --  Loop_Actions to collect inserted actions that may be crated.
 
       if No (Expressions (N)) then
 
@@ -1073,22 +1215,35 @@ package body Exp_Aggr is
 
          Assoc := First (Component_Associations (N));
          while Present (Assoc) loop
-
             Choice := First (Choices (Assoc));
             while Present (Choice) loop
-
                if Nkind (Choice) = N_Others_Choice then
-                  Others_Expr := Expression (Assoc);
+                  Set_Loop_Actions (Assoc, New_List);
+
+                  if Box_Present (Assoc) then
+                     Others_Mbox_Present := True;
+                  else
+                     Others_Expr := Expression (Assoc);
+                  end if;
                   exit;
                end if;
 
                Get_Index_Bounds (Choice, Low, High);
 
-               Nb_Choices := Nb_Choices + 1;
-               Table (Nb_Choices) := (Choice_Lo   => Low,
-                                      Choice_Hi   => High,
-                                      Choice_Node => Expression (Assoc));
+               if Low /= High then
+                  Set_Loop_Actions (Assoc, New_List);
+               end if;
 
+               Nb_Choices := Nb_Choices + 1;
+               if Box_Present (Assoc) then
+                  Table (Nb_Choices) := (Choice_Lo   => Low,
+                                         Choice_Hi   => High,
+                                         Choice_Node => Empty);
+               else
+                  Table (Nb_Choices) := (Choice_Lo   => Low,
+                                         Choice_Hi   => High,
+                                         Choice_Node => Expression (Assoc));
+               end if;
                Next (Choice);
             end loop;
 
@@ -1109,7 +1264,6 @@ package body Exp_Aggr is
             Low  := Table (J).Choice_Lo;
             High := Table (J).Choice_Hi;
             Expr := Table (J).Choice_Node;
-
             Append_List (Gen_Loop (Low, High, Expr), To => New_Code);
          end loop;
 
@@ -1117,13 +1271,12 @@ package body Exp_Aggr is
          --  We don't need to generate loops over empty gaps, but if there is
          --  a single empty range we must analyze the expression for semantics
 
-         if Present (Others_Expr) then
+         if Present (Others_Expr) or else Others_Mbox_Present then
             declare
                First : Boolean := True;
 
             begin
                for J in 0 .. Nb_Choices loop
-
                   if J = 0 then
                      Low := Aggr_Low;
                   else
@@ -1136,7 +1289,7 @@ package body Exp_Aggr is
                      High := Add (-1, To => Table (J + 1).Choice_Lo);
                   end if;
 
-                  --  If this is an expansion within an init_proc, make
+                  --  If this is an expansion within an init proc, make
                   --  sure that discriminant references are replaced by
                   --  the corresponding discriminal.
 
@@ -1187,12 +1340,22 @@ package body Exp_Aggr is
 
          if Present (Component_Associations (N)) then
             Assoc := Last (Component_Associations (N));
-            Expr  := Expression (Assoc);
 
-            Append_List (Gen_While (Add (Nb_Elements, To => Aggr_L),
-                                    Aggr_High,
-                                    Expr),
-                         To => New_Code);
+            --  Ada 2005 (AI-287)
+
+            if Box_Present (Assoc) then
+               Append_List (Gen_While (Add (Nb_Elements, To => Aggr_L),
+                                       Aggr_High,
+                                       Empty),
+                            To => New_Code);
+            else
+               Expr  := Expression (Assoc);
+
+               Append_List (Gen_While (Add (Nb_Elements, To => Aggr_L),
+                                       Aggr_High,
+                                       Expr), --  AI-287
+                            To => New_Code);
+            end if;
          end if;
       end if;
 
@@ -1204,12 +1367,12 @@ package body Exp_Aggr is
    ----------------------------
 
    function Build_Record_Aggr_Code
-     (N      : Node_Id;
-      Typ    : Entity_Id;
-      Target : Node_Id;
-      Flist  : Node_Id   := Empty;
-      Obj    : Entity_Id := Empty)
-      return   List_Id
+     (N                             : Node_Id;
+      Typ                           : Entity_Id;
+      Target                        : Node_Id;
+      Flist                         : Node_Id   := Empty;
+      Obj                           : Entity_Id := Empty;
+      Is_Limited_Ancestor_Expansion : Boolean   := False) return List_Id
    is
       Loc     : constant Source_Ptr := Sloc (N);
       L       : constant List_Id    := New_List;
@@ -1223,7 +1386,6 @@ package body Exp_Aggr is
       Comp_Type : Entity_Id;
       Selector  : Entity_Id;
       Comp_Expr : Node_Id;
-      Comp_Kind : Node_Kind;
       Expr_Q    : Node_Id;
 
       Internal_Final_List : Node_Id;
@@ -1261,12 +1423,11 @@ package body Exp_Aggr is
          Typ     : Entity_Id;
          F       : Node_Id;
          Attach  : Node_Id;
-         Init_Pr : Boolean)
-        return List_Id;
+         Init_Pr : Boolean) return List_Id;
       --  returns the list of statements necessary to initialize the internal
       --  controller of the (possible) ancestor typ into target and attach
       --  it to finalization list F. Init_Pr conditions the call to the
-      --  init_proc since it may already be done due to ancestor initialization
+      --  init proc since it may already be done due to ancestor initialization
 
       ---------------------------------
       -- Ancestor_Discriminant_Value --
@@ -1303,6 +1464,7 @@ package body Exp_Aggr is
                      if Disc = Corresp_Disc then
                         return Duplicate_Subexpr (Expression (Assoc));
                      end if;
+
                      Corresp_Disc :=
                        Corresponding_Discriminant (Corresp_Disc);
                   end loop;
@@ -1417,8 +1579,10 @@ package body Exp_Aggr is
                      Selector_Name => New_Occurrence_Of (Discr, Loc)),
                  Right_Opnd => Disc_Value);
 
-               Append_To (L, Make_Raise_Constraint_Error (Loc,
-                                                          Condition => Cond));
+               Append_To (L,
+                 Make_Raise_Constraint_Error (Loc,
+                   Condition => Cond,
+                   Reason    => CE_Discriminant_Check_Failed));
             end if;
 
             Next_Discriminant (Discr);
@@ -1455,36 +1619,76 @@ package body Exp_Aggr is
          Typ     : Entity_Id;
          F       : Node_Id;
          Attach  : Node_Id;
-         Init_Pr : Boolean)
-        return List_Id
+         Init_Pr : Boolean) return List_Id
       is
+         L   : constant List_Id := New_List;
          Ref : Node_Id;
-         L   : List_Id := New_List;
 
       begin
-         --     _init_proc (target._controller);
+         --  Generate:
+         --     init-proc (target._controller);
          --     initialize (target._controller);
          --     Attach_to_Final_List (target._controller, F);
 
-         Ref := Make_Selected_Component (Loc,
-                  Prefix        => Convert_To (Typ, New_Copy_Tree (Target)),
-                  Selector_Name => Make_Identifier (Loc, Name_uController));
+         Ref :=
+           Make_Selected_Component (Loc,
+             Prefix        => Convert_To (Typ, New_Copy_Tree (Target)),
+             Selector_Name => Make_Identifier (Loc, Name_uController));
          Set_Assignment_OK (Ref);
 
-         if Init_Pr then
-            Append_List_To (L,
-              Build_Initialization_Call (Loc,
-                Id_Ref       => Ref,
-                Typ          => RTE (RE_Record_Controller),
-                In_Init_Proc => Within_Init_Proc));
-         end if;
+         --  Ada 2005 (AI-287): Give support to default initialization of
+         --  limited types and components.
 
-         Append_To (L,
-           Make_Procedure_Call_Statement (Loc,
-             Name =>
-               New_Reference_To (Find_Prim_Op (RTE (RE_Record_Controller),
-                 Name_Initialize), Loc),
-             Parameter_Associations => New_List (New_Copy_Tree (Ref))));
+         if (Nkind (Target) = N_Identifier
+              and then Present (Etype (Target))
+              and then Is_Limited_Type (Etype (Target)))
+           or else
+            (Nkind (Target) = N_Selected_Component
+              and then Present (Etype (Selector_Name (Target)))
+              and then Is_Limited_Type (Etype (Selector_Name (Target))))
+           or else
+            (Nkind (Target) = N_Unchecked_Type_Conversion
+              and then Present (Etype (Target))
+              and then Is_Limited_Type (Etype (Target)))
+           or else
+            (Nkind (Target) = N_Unchecked_Expression
+              and then Nkind (Expression (Target)) = N_Indexed_Component
+              and then Present (Etype (Prefix (Expression (Target))))
+              and then Is_Limited_Type (Etype (Prefix (Expression (Target)))))
+         then
+            if Init_Pr then
+               Append_List_To (L,
+                 Build_Initialization_Call (Loc,
+                   Id_Ref       => Ref,
+                   Typ          => RTE (RE_Limited_Record_Controller),
+                   In_Init_Proc => Within_Init_Proc));
+            end if;
+
+            Append_To (L,
+              Make_Procedure_Call_Statement (Loc,
+                Name =>
+                  New_Reference_To
+                         (Find_Prim_Op (RTE (RE_Limited_Record_Controller),
+                    Name_Initialize), Loc),
+                Parameter_Associations => New_List (New_Copy_Tree (Ref))));
+
+         else
+            if Init_Pr then
+               Append_List_To (L,
+                 Build_Initialization_Call (Loc,
+                   Id_Ref       => Ref,
+                   Typ          => RTE (RE_Record_Controller),
+                   In_Init_Proc => Within_Init_Proc));
+            end if;
+
+            Append_To (L,
+              Make_Procedure_Call_Statement (Loc,
+                Name =>
+                  New_Reference_To (Find_Prim_Op (RTE (RE_Record_Controller),
+                    Name_Initialize), Loc),
+                Parameter_Associations => New_List (New_Copy_Tree (Ref))));
+
+         end if;
 
          Append_To (L,
            Make_Attach_Call (
@@ -1497,7 +1701,6 @@ package body Exp_Aggr is
    --  Start of processing for Build_Record_Aggr_Code
 
    begin
-
       --  Deal with the ancestor part of extension aggregates
       --  or with the discriminants of the root type
 
@@ -1506,14 +1709,13 @@ package body Exp_Aggr is
             A : constant Node_Id := Ancestor_Part (N);
 
          begin
-
             --  If the ancestor part is a subtype mark "T", we generate
-            --     _init_proc (T(tmp));  if T is constrained and
-            --     _init_proc (S(tmp));  where S applies an appropriate
+
+            --     init-proc (T(tmp));  if T is constrained and
+            --     init-proc (S(tmp));  where S applies an appropriate
             --                           constraint if T is unconstrained
 
             if Is_Entity_Name (A) and then Is_Type (Entity (A)) then
-
                Ancestor_Is_Subtype_Mark := True;
 
                if Is_Constrained (Entity (A)) then
@@ -1528,13 +1730,15 @@ package body Exp_Aggr is
 
                elsif Has_Discriminants (Entity (A)) then
                   declare
-                     Anc_Typ    : Entity_Id := Entity (A);
-                     Discrim    : Entity_Id := First_Discriminant (Anc_Typ);
-                     Anc_Constr : List_Id := New_List;
+                     Anc_Typ    : constant Entity_Id := Entity (A);
+                     Anc_Constr : constant List_Id   := New_List;
+                     Discrim    : Entity_Id;
                      Disc_Value : Node_Id;
                      New_Indic  : Node_Id;
                      Subt_Decl  : Node_Id;
+
                   begin
+                     Discrim := First_Discriminant (Anc_Typ);
                      while Present (Discrim) loop
                         Disc_Value := Ancestor_Discriminant_Value (Discrim);
                         Append_To (Anc_Constr, Disc_Value);
@@ -1556,7 +1760,10 @@ package body Exp_Aggr is
                          Subtype_Indication  => New_Indic);
 
                      --  Itypes must be analyzed with checks off
+                     --  Declaration must have a parent for proper
+                     --  handling of subsidiary actions.
 
+                     Set_Parent (Subt_Decl, N);
                      Analyze (Subt_Decl, Suppress => All_Checks);
                   end;
                end if;
@@ -1564,11 +1771,22 @@ package body Exp_Aggr is
                Ref := Convert_To (Init_Typ, New_Copy_Tree (Target));
                Set_Assignment_OK (Ref);
 
-               Append_List_To (Start_L,
-                 Build_Initialization_Call (Loc,
-                   Id_Ref => Ref,
-                   Typ    => Init_Typ,
-                   In_Init_Proc => Within_Init_Proc));
+               if Has_Default_Init_Comps (N)
+                 or else Has_Task (Base_Type (Init_Typ))
+               then
+                  Append_List_To (Start_L,
+                    Build_Initialization_Call (Loc,
+                      Id_Ref       => Ref,
+                      Typ          => Init_Typ,
+                      In_Init_Proc => Within_Init_Proc,
+                      With_Default_Init => True));
+               else
+                  Append_List_To (Start_L,
+                    Build_Initialization_Call (Loc,
+                      Id_Ref       => Ref,
+                      Typ          => Init_Typ,
+                      In_Init_Proc => Within_Init_Proc));
+               end if;
 
                if Is_Constrained (Entity (A))
                  and then Has_Discriminants (Entity (A))
@@ -1576,6 +1794,21 @@ package body Exp_Aggr is
                   Check_Ancestor_Discriminants (Entity (A));
                end if;
 
+            --  Ada 2005 (AI-287): If the ancestor part is a limited type,
+            --  a recursive call expands the ancestor.
+
+            elsif Is_Limited_Type (Etype (A)) then
+               Ancestor_Is_Expression := True;
+
+               Append_List_To (Start_L,
+                  Build_Record_Aggr_Code (
+                    N                             => Expression (A),
+                    Typ                           => Etype (Expression (A)),
+                    Target                        => Target,
+                    Flist                         => Flist,
+                    Obj                           => Obj,
+                    Is_Limited_Ancestor_Expansion => True));
+
             --  If the ancestor part is an expression "E", we generate
             --     T(tmp) := E;
 
@@ -1633,6 +1866,8 @@ package body Exp_Aggr is
             end if;
          end;
 
+      --  Normal case (not an extension aggregate)
+
       else
          --  Generate the discriminant expressions, component by component.
          --  If the base type is an unchecked union, the discriminants are
@@ -1642,7 +1877,6 @@ package body Exp_Aggr is
          if Has_Discriminants (Typ)
            and then not Is_Unchecked_Union (Base_Type (Typ))
          then
-
             --  ??? The discriminants of the object not inherited in the type
             --  of the object should be initialized here
 
@@ -1655,7 +1889,7 @@ package body Exp_Aggr is
                Discriminant_Value : Node_Id;
 
             begin
-               Discriminant := First_Girder_Discriminant (Typ);
+               Discriminant := First_Stored_Discriminant (Typ);
 
                while Present (Discriminant) loop
 
@@ -1678,7 +1912,7 @@ package body Exp_Aggr is
                   Set_No_Ctrl_Actions (Instr);
                   Append_To (L, Instr);
 
-                  Next_Girder_Discriminant (Discriminant);
+                  Next_Stored_Discriminant (Discriminant);
                end loop;
             end;
          end if;
@@ -1692,13 +1926,62 @@ package body Exp_Aggr is
 
       Comp := First (Component_Associations (N));
       while Present (Comp) loop
-         Selector  := Entity (First (Choices (Comp)));
+         Selector := Entity (First (Choices (Comp)));
+
+         --  Ada 2005 (AI-287): Default initialization of a limited component
+
+         if Box_Present (Comp)
+            and then Is_Limited_Type (Etype (Selector))
+         then
+            --  Ada 2005 (AI-287): If the component type has tasks then
+            --  generate the activation chain and master entities (except
+            --  in case of an allocator because in that case these entities
+            --  are generated by Build_Task_Allocate_Block_With_Init_Stmts).
+
+            declare
+               Ctype            : constant Entity_Id := Etype (Selector);
+               Inside_Allocator : Boolean   := False;
+               P                : Node_Id   := Parent (N);
+
+            begin
+               if Is_Task_Type (Ctype) or else Has_Task (Ctype) then
+                  while Present (P) loop
+                     if Nkind (P) = N_Allocator then
+                        Inside_Allocator := True;
+                        exit;
+                     end if;
+
+                     P := Parent (P);
+                  end loop;
+
+                  if not Inside_Init_Proc and not Inside_Allocator then
+                     Build_Activation_Chain_Entity (N);
+
+                     if not Has_Master_Entity (Current_Scope) then
+                        Build_Master_Entity (Etype (N));
+                     end if;
+                  end if;
+               end if;
+            end;
+
+            Append_List_To (L,
+              Build_Initialization_Call (Loc,
+                Id_Ref => Make_Selected_Component (Loc,
+                            Prefix => New_Copy_Tree (Target),
+                            Selector_Name => New_Occurrence_Of (Selector,
+                                                                   Loc)),
+                Typ    => Etype (Selector),
+                With_Default_Init => True));
+
+            goto Next_Comp;
+         end if;
+
+         --  ???
 
          if Ekind (Selector) /= E_Discriminant
            or else Nkind (N) = N_Extension_Aggregate
          then
             Comp_Type := Etype (Selector);
-            Comp_Kind := Nkind (Expression (Comp));
             Comp_Expr :=
               Make_Selected_Component (Loc,
                 Prefix        => New_Copy_Tree (Target),
@@ -1721,6 +2004,7 @@ package body Exp_Aggr is
                      New_Copy_Tree (Target)),
                    Selector_Name =>
                      Make_Identifier (Loc, Name_uController));
+
                Internal_Final_List :=
                  Make_Selected_Component (Loc,
                    Prefix => Internal_Final_List,
@@ -1729,14 +2013,18 @@ package body Exp_Aggr is
                --  The internal final list can be part of a constant object
 
                Set_Assignment_OK (Internal_Final_List);
+
             else
                Internal_Final_List := Empty;
             end if;
 
+            --  ???
+
             if Is_Delayed_Aggregate (Expr_Q) then
                Append_List_To (L,
                  Late_Expansion (Expr_Q, Comp_Type, Comp_Expr,
                    Internal_Final_List));
+
             else
                Instr :=
                  Make_OK_Assignment_Statement (Loc,
@@ -1783,15 +2071,53 @@ package body Exp_Aggr is
                       With_Attach => Make_Integer_Literal (Loc, 1)));
                end if;
             end if;
+
+         --  ???
+
+         elsif Ekind (Selector) = E_Discriminant
+           and then Nkind (N) /= N_Extension_Aggregate
+           and then Nkind (Parent (N)) = N_Component_Association
+           and then Is_Constrained (Typ)
+         then
+            --  We must check that the discriminant value imposed by the
+            --  context is the same as the value given in the subaggregate,
+            --  because after the expansion into assignments there is no
+            --  record on which to perform a regular discriminant check.
+
+            declare
+               D_Val : Elmt_Id;
+               Disc  : Entity_Id;
+
+            begin
+               D_Val := First_Elmt (Discriminant_Constraint (Typ));
+               Disc  := First_Discriminant (Typ);
+
+               while Chars (Disc) /= Chars (Selector) loop
+                  Next_Discriminant (Disc);
+                  Next_Elmt (D_Val);
+               end loop;
+
+               pragma Assert (Present (D_Val));
+
+               Append_To (L,
+               Make_Raise_Constraint_Error (Loc,
+                 Condition =>
+                   Make_Op_Ne (Loc,
+                     Left_Opnd => New_Copy_Tree (Node (D_Val)),
+                     Right_Opnd => Expression (Comp)),
+                 Reason => CE_Discriminant_Check_Failed));
+            end;
          end if;
 
+         <<Next_Comp>>
+
          Next (Comp);
       end loop;
 
       --  If the type is tagged, the tag needs to be initialized (unless
       --  compiling for the Java VM where tags are implicit). It is done
       --  late in the initialization process because in some cases, we call
-      --  the init_proc of an ancestor which will not leave out the right tag
+      --  the init proc of an ancestor which will not leave out the right tag
 
       if Ancestor_Is_Expression then
          null;
@@ -1855,8 +2181,7 @@ package body Exp_Aggr is
          External_Final_List := Empty;
       end if;
 
-      --  initialize and attach the outer object in the is_controlled
-      --  case
+      --  Initialize and attach the outer object in the is_controlled case
 
       if Is_Controlled (Typ) then
          if Ancestor_Is_Subtype_Mark then
@@ -1869,33 +2194,7 @@ package body Exp_Aggr is
                 Parameter_Associations => New_List (New_Copy_Tree (Ref))));
          end if;
 
-         --  ??? when the ancestor part is an expression, the global
-         --  object is already attached at the wrong level. It should
-         --  be detached and re-attached. We have a design problem here.
-
-         if Ancestor_Is_Expression
-           and then Has_Controlled_Component (Init_Typ)
-         then
-            null;
-
-         elsif Has_Controlled_Component (Typ) then
-            F := Make_Selected_Component (Loc,
-                   Prefix        => New_Copy_Tree (Target),
-                   Selector_Name => Make_Identifier (Loc, Name_uController));
-            F := Make_Selected_Component (Loc,
-                   Prefix        => F,
-                   Selector_Name => Make_Identifier (Loc, Name_F));
-
-            Ref := New_Copy_Tree (Target);
-            Set_Assignment_OK (Ref);
-
-            Append_To (L,
-              Make_Attach_Call (
-                Obj_Ref     => Ref,
-                Flist_Ref   => F,
-                With_Attach => Make_Integer_Literal (Loc, 1)));
-
-         else --  is_Controlled (Typ) and not Has_Controlled_Component (Typ)
+         if not Has_Controlled_Component (Typ) then
             Ref := New_Copy_Tree (Target);
             Set_Assignment_OK (Ref);
             Append_To (Start_L,
@@ -1906,10 +2205,12 @@ package body Exp_Aggr is
          end if;
       end if;
 
-      --  in the Has_Controlled component case, all the intermediate
+      --  In the Has_Controlled component case, all the intermediate
       --  controllers must be initialized
 
-      if Has_Controlled_Component (Typ) then
+      if Has_Controlled_Component (Typ)
+        and not Is_Limited_Ancestor_Expansion
+      then
          declare
             Inner_Typ : Entity_Id;
             Outer_Typ : Entity_Id;
@@ -1919,7 +2220,7 @@ package body Exp_Aggr is
 
             Outer_Typ := Base_Type (Typ);
 
-            --  find outer type with a controller
+            --  Find outer type with a controller
 
             while Outer_Typ /= Init_Typ
               and then not Has_New_Controlled_Component (Outer_Typ)
@@ -1927,7 +2228,7 @@ package body Exp_Aggr is
                Outer_Typ := Etype (Outer_Typ);
             end loop;
 
-            --  attach it to the outer record controller to the
+            --  Attach it to the outer record controller to the
             --  external final list
 
             if Outer_Typ = Init_Typ then
@@ -1938,7 +2239,8 @@ package body Exp_Aggr is
                    F       => External_Final_List,
                    Attach  => Attach,
                    Init_Pr => Ancestor_Is_Expression));
-               At_Root := True;
+
+               At_Root   := True;
                Inner_Typ := Init_Typ;
 
             else
@@ -1955,6 +2257,18 @@ package body Exp_Aggr is
                  not Is_Tagged_Type (Typ) or else Inner_Typ = Outer_Typ;
             end if;
 
+            --  The outer object has to be attached as well
+
+            if Is_Controlled (Typ) then
+               Ref := New_Copy_Tree (Target);
+               Set_Assignment_OK (Ref);
+               Append_To (Start_L,
+                  Make_Attach_Call (
+                    Obj_Ref     => Ref,
+                    Flist_Ref   => New_Copy_Tree (External_Final_List),
+                    With_Attach => New_Copy_Tree (Attach)));
+            end if;
+
             --  Initialize the internal controllers for tagged types with
             --  more than one controller.
 
@@ -1965,9 +2279,11 @@ package body Exp_Aggr is
                       Prefix => Convert_To (Outer_Typ, New_Copy_Tree (Target)),
                       Selector_Name =>
                         Make_Identifier (Loc, Name_uController));
-                  F := Make_Selected_Component (Loc,
-                         Prefix => F,
-                         Selector_Name => Make_Identifier (Loc, Name_F));
+                  F :=
+                    Make_Selected_Component (Loc,
+                      Prefix => F,
+                      Selector_Name => Make_Identifier (Loc, Name_F));
+
                   Append_List_To (Start_L,
                     Init_Controller (
                       Target  => Target,
@@ -1984,7 +2300,7 @@ package body Exp_Aggr is
                Inner_Typ := Etype (Inner_Typ);
             end loop;
 
-            --  if not done yet attach the controller of the ancestor part
+            --  If not done yet attach the controller of the ancestor part
 
             if Outer_Typ /= Init_Typ
               and then Inner_Typ = Init_Typ
@@ -1994,9 +2310,10 @@ package body Exp_Aggr is
                   Make_Selected_Component (Loc,
                     Prefix => Convert_To (Outer_Typ, New_Copy_Tree (Target)),
                     Selector_Name => Make_Identifier (Loc, Name_uController));
-               F := Make_Selected_Component (Loc,
-                       Prefix => F,
-                       Selector_Name => Make_Identifier (Loc, Name_F));
+               F :=
+                  Make_Selected_Component (Loc,
+                    Prefix => F,
+                    Selector_Name => Make_Identifier (Loc, Name_F));
 
                Attach := Make_Integer_Literal (Loc, 1);
                Append_List_To (Start_L,
@@ -2022,16 +2339,35 @@ package body Exp_Aggr is
       Loc  : constant Source_Ptr := Sloc (Aggr);
       Typ  : constant Entity_Id  := Etype (Aggr);
       Temp : constant Entity_Id  := Defining_Identifier (Decl);
-      Occ  : constant Node_Id    := Unchecked_Convert_To (Typ,
-        Make_Explicit_Dereference (Loc, New_Reference_To (Temp, Loc)));
+
+      Occ  : constant Node_Id :=
+               Unchecked_Convert_To (Typ,
+                 Make_Explicit_Dereference (Loc,
+                   New_Reference_To (Temp, Loc)));
 
       Access_Type : constant Entity_Id := Etype (Temp);
 
    begin
-      Insert_Actions_After (Decl,
-        Late_Expansion (Aggr, Typ, Occ,
-          Find_Final_List (Access_Type),
-          Associated_Final_Chain (Base_Type (Access_Type))));
+      if Has_Default_Init_Comps (Aggr) then
+         declare
+            L          : constant List_Id := New_List;
+            Init_Stmts : List_Id;
+
+         begin
+            Init_Stmts := Late_Expansion (Aggr, Typ, Occ,
+                            Find_Final_List (Access_Type),
+                            Associated_Final_Chain (Base_Type (Access_Type)));
+
+            Build_Task_Allocate_Block_With_Init_Stmts (L, Aggr, Init_Stmts);
+            Insert_Actions_After (Decl, L);
+         end;
+
+      else
+         Insert_Actions_After (Decl,
+           Late_Expansion (Aggr, Typ, Occ,
+             Find_Final_List (Access_Type),
+             Associated_Final_Chain (Base_Type (Access_Type))));
+      end if;
    end Convert_Aggr_In_Allocator;
 
    --------------------------------
@@ -2039,7 +2375,7 @@ package body Exp_Aggr is
    --------------------------------
 
    procedure Convert_Aggr_In_Assignment (N : Node_Id) is
-      Aggr :          Node_Id    := Expression (N);
+      Aggr : Node_Id             := Expression (N);
       Typ  : constant Entity_Id  := Etype (Aggr);
       Occ  : constant Node_Id    := New_Copy_Tree (Name (N));
 
@@ -2059,40 +2395,119 @@ package body Exp_Aggr is
 
    procedure Convert_Aggr_In_Object_Decl (N : Node_Id) is
       Obj  : constant Entity_Id  := Defining_Identifier (N);
-      Aggr :          Node_Id    := Expression (N);
+      Aggr : Node_Id             := Expression (N);
       Loc  : constant Source_Ptr := Sloc (Aggr);
       Typ  : constant Entity_Id  := Etype (Aggr);
       Occ  : constant Node_Id    := New_Occurrence_Of (Obj, Loc);
 
-   begin
-      Set_Assignment_OK (Occ);
+      function Discriminants_Ok return Boolean;
+      --  If the object type is constrained, the discriminants in the
+      --  aggregate must be checked against the discriminants of the subtype.
+      --  This cannot be done using Apply_Discriminant_Checks because after
+      --  expansion there is no aggregate left to check.
 
-      if Nkind (Aggr) = N_Qualified_Expression then
-         Aggr := Expression (Aggr);
-      end if;
+      ----------------------
+      -- Discriminants_Ok --
+      ----------------------
 
-      Insert_Actions_After (N, Late_Expansion (Aggr, Typ, Occ, Obj => Obj));
-      Set_No_Initialization (N);
-   end Convert_Aggr_In_Object_Decl;
+      function Discriminants_Ok return Boolean is
+         Cond  : Node_Id := Empty;
+         Check : Node_Id;
+         D     : Entity_Id;
+         Disc1 : Elmt_Id;
+         Disc2 : Elmt_Id;
+         Val1  : Node_Id;
+         Val2  : Node_Id;
 
-   ----------------------------
-   -- Convert_To_Assignments --
-   ----------------------------
+      begin
+         D := First_Discriminant (Typ);
+         Disc1 := First_Elmt (Discriminant_Constraint (Typ));
+         Disc2 := First_Elmt (Discriminant_Constraint (Etype (Obj)));
 
-   procedure Convert_To_Assignments (N : Node_Id; Typ : Entity_Id) is
-      Loc  : constant Source_Ptr := Sloc (N);
-      Temp : Entity_Id;
+         while Present (Disc1) and then Present (Disc2) loop
+            Val1 := Node (Disc1);
+            Val2 := Node (Disc2);
 
-      Instr         : Node_Id;
-      Target_Expr   : Node_Id;
-      Parent_Kind   : Node_Kind;
-      Unc_Decl      : Boolean := False;
-      Parent_Node   : Node_Id;
+            if not Is_OK_Static_Expression (Val1)
+              or else not Is_OK_Static_Expression (Val2)
+            then
+               Check := Make_Op_Ne (Loc,
+                 Left_Opnd  => Duplicate_Subexpr (Val1),
+                 Right_Opnd => Duplicate_Subexpr (Val2));
 
-   begin
+               if No (Cond) then
+                  Cond := Check;
 
-      Parent_Node := Parent (N);
-      Parent_Kind := Nkind (Parent_Node);
+               else
+                  Cond := Make_Or_Else (Loc,
+                    Left_Opnd => Cond,
+                    Right_Opnd => Check);
+               end if;
+
+            elsif Expr_Value (Val1) /= Expr_Value (Val2) then
+               Apply_Compile_Time_Constraint_Error (Aggr,
+                 Msg    => "incorrect value for discriminant&?",
+                 Reason => CE_Discriminant_Check_Failed,
+                 Ent    => D);
+               return False;
+            end if;
+
+            Next_Discriminant (D);
+            Next_Elmt (Disc1);
+            Next_Elmt (Disc2);
+         end loop;
+
+         --  If any discriminant constraint is non-static, emit a check.
+
+         if Present (Cond) then
+            Insert_Action (N,
+              Make_Raise_Constraint_Error (Loc,
+                Condition => Cond,
+                Reason => CE_Discriminant_Check_Failed));
+         end if;
+
+         return True;
+      end Discriminants_Ok;
+
+   --  Start of processing for Convert_Aggr_In_Object_Decl
+
+   begin
+      Set_Assignment_OK (Occ);
+
+      if Nkind (Aggr) = N_Qualified_Expression then
+         Aggr := Expression (Aggr);
+      end if;
+
+      if Has_Discriminants (Typ)
+        and then Typ /= Etype (Obj)
+        and then Is_Constrained (Etype (Obj))
+        and then not Discriminants_Ok
+      then
+         return;
+      end if;
+
+      Insert_Actions_After (N, Late_Expansion (Aggr, Typ, Occ, Obj => Obj));
+      Set_No_Initialization (N);
+      Initialize_Discriminants (N, Typ);
+   end Convert_Aggr_In_Object_Decl;
+
+   ----------------------------
+   -- Convert_To_Assignments --
+   ----------------------------
+
+   procedure Convert_To_Assignments (N : Node_Id; Typ : Entity_Id) is
+      Loc  : constant Source_Ptr := Sloc (N);
+      Temp : Entity_Id;
+
+      Instr       : Node_Id;
+      Target_Expr : Node_Id;
+      Parent_Kind : Node_Kind;
+      Unc_Decl    : Boolean := False;
+      Parent_Node : Node_Id;
+
+   begin
+      Parent_Node := Parent (N);
+      Parent_Kind := Nkind (Parent_Node);
 
       if Parent_Kind = N_Qualified_Expression then
 
@@ -2103,24 +2518,26 @@ package body Exp_Aggr is
          begin
             Parent_Node := Parent (Parent_Node);
             Parent_Kind := Nkind (Parent_Node);
+
             if Parent_Kind = N_Object_Declaration then
                Unc_Decl :=
                  not Is_Entity_Name (Object_Definition (Parent_Node))
-                 or else Has_Discriminants (
-                   Entity (Object_Definition (Parent_Node)))
-                 or else Is_Class_Wide_Type (
-                   Entity (Object_Definition (Parent_Node)));
+                   or else Has_Discriminants
+                             (Entity (Object_Definition (Parent_Node)))
+                   or else Is_Class_Wide_Type
+                             (Entity (Object_Definition (Parent_Node)));
             end if;
          end;
       end if;
 
       --  Just set the Delay flag in the following cases where the
       --  transformation will be done top down from above
+
       --    - internal aggregate (transformed when expanding the parent)
       --    - allocators  (see Convert_Aggr_In_Allocator)
       --    - object decl (see Convert_Aggr_In_Object_Decl)
       --    - safe assignments (see Convert_Aggr_Assignments)
-      --      so far only the assignments in the init_procs are taken
+      --      so far only the assignments in the init procs are taken
       --      into account
 
       if Parent_Kind = N_Aggregate
@@ -2151,6 +2568,7 @@ package body Exp_Aggr is
 
       Set_No_Initialization (Instr);
       Insert_Action (N, Instr);
+      Initialize_Discriminants (Instr, Typ);
       Target_Expr := New_Occurrence_Of (Temp, Loc);
 
       Insert_Actions (N, Build_Record_Aggr_Code (N, Typ, Target_Expr));
@@ -2158,6 +2576,332 @@ package body Exp_Aggr is
       Analyze_And_Resolve (N, Typ);
    end Convert_To_Assignments;
 
+   ---------------------------
+   -- Convert_To_Positional --
+   ---------------------------
+
+   procedure Convert_To_Positional
+     (N                    : Node_Id;
+      Max_Others_Replicate : Nat     := 5;
+      Handle_Bit_Packed    : Boolean := False)
+   is
+      Typ : constant Entity_Id := Etype (N);
+
+      function Flatten
+        (N   : Node_Id;
+         Ix  : Node_Id;
+         Ixb : Node_Id) return Boolean;
+      --  Convert the aggregate into a purely positional form if possible.
+
+      function Is_Flat (N : Node_Id; Dims : Int) return Boolean;
+      --  Non trivial for multidimensional aggregate.
+
+      -------------
+      -- Flatten --
+      -------------
+
+      function Flatten
+        (N   : Node_Id;
+         Ix  : Node_Id;
+         Ixb : Node_Id) return Boolean
+      is
+         Loc : constant Source_Ptr := Sloc (N);
+         Blo : constant Node_Id    := Type_Low_Bound (Etype (Ixb));
+         Lo  : constant Node_Id    := Type_Low_Bound (Etype (Ix));
+         Hi  : constant Node_Id    := Type_High_Bound (Etype (Ix));
+         Lov : Uint;
+         Hiv : Uint;
+
+         --  The following constant determines the maximum size of an
+         --  aggregate produced by converting named to positional
+         --  notation (e.g. from others clauses). This avoids running
+         --  away with attempts to convert huge aggregates.
+
+         --  The normal limit is 5000, but we increase this limit to
+         --  2**24 (about 16 million) if Restrictions (No_Elaboration_Code)
+         --  or Restrictions (No_Implicit_Loops) is specified, since in
+         --  either case, we are at risk of declaring the program illegal
+         --  because of this limit.
+
+         Max_Aggr_Size : constant Nat :=
+                           5000 + (2 ** 24 - 5000) *
+                             Boolean'Pos
+                               (Restriction_Active (No_Elaboration_Code)
+                                  or else
+                                Restriction_Active (No_Implicit_Loops));
+
+      begin
+         if Nkind (Original_Node (N)) = N_String_Literal then
+            return True;
+         end if;
+
+         --  Bounds need to be known at compile time
+
+         if not Compile_Time_Known_Value (Lo)
+           or else not Compile_Time_Known_Value (Hi)
+         then
+            return False;
+         end if;
+
+         --  Get bounds and check reasonable size (positive, not too large)
+         --  Also only handle bounds starting at the base type low bound
+         --  for now since the compiler isn't able to handle different low
+         --  bounds yet. Case such as new String'(3..5 => ' ') will get
+         --  the wrong bounds, though it seems that the aggregate should
+         --  retain the bounds set on its Etype (see C64103E and CC1311B).
+
+         Lov := Expr_Value (Lo);
+         Hiv := Expr_Value (Hi);
+
+         if Hiv < Lov
+           or else (Hiv - Lov > Max_Aggr_Size)
+           or else not Compile_Time_Known_Value (Blo)
+           or else (Lov /= Expr_Value (Blo))
+         then
+            return False;
+         end if;
+
+         --  Bounds must be in integer range (for array Vals below)
+
+         if not UI_Is_In_Int_Range (Lov)
+             or else
+            not UI_Is_In_Int_Range (Hiv)
+         then
+            return False;
+         end if;
+
+         --  Determine if set of alternatives is suitable for conversion
+         --  and build an array containing the values in sequence.
+
+         declare
+            Vals : array (UI_To_Int (Lov) .. UI_To_Int (Hiv))
+                     of Node_Id := (others => Empty);
+            --  The values in the aggregate sorted appropriately
+
+            Vlist : List_Id;
+            --  Same data as Vals in list form
+
+            Rep_Count : Nat;
+            --  Used to validate Max_Others_Replicate limit
+
+            Elmt   : Node_Id;
+            Num    : Int := UI_To_Int (Lov);
+            Choice : Node_Id;
+            Lo, Hi : Node_Id;
+
+         begin
+            if Present (Expressions (N)) then
+               Elmt := First (Expressions (N));
+
+               while Present (Elmt) loop
+                  if Nkind (Elmt) = N_Aggregate
+                    and then Present (Next_Index (Ix))
+                    and then
+                         not Flatten (Elmt, Next_Index (Ix), Next_Index (Ixb))
+                  then
+                     return False;
+                  end if;
+
+                  Vals (Num) := Relocate_Node (Elmt);
+                  Num := Num + 1;
+
+                  Next (Elmt);
+               end loop;
+            end if;
+
+            if No (Component_Associations (N)) then
+               return True;
+            end if;
+
+            Elmt := First (Component_Associations (N));
+
+            if Nkind (Expression (Elmt)) = N_Aggregate then
+               if Present (Next_Index (Ix))
+                 and then
+                   not Flatten
+                        (Expression (Elmt), Next_Index (Ix), Next_Index (Ixb))
+               then
+                  return False;
+               end if;
+            end if;
+
+            Component_Loop : while Present (Elmt) loop
+               Choice := First (Choices (Elmt));
+               Choice_Loop : while Present (Choice) loop
+
+                  --  If we have an others choice, fill in the missing elements
+                  --  subject to the limit established by Max_Others_Replicate.
+
+                  if Nkind (Choice) = N_Others_Choice then
+                     Rep_Count := 0;
+
+                     for J in Vals'Range loop
+                        if No (Vals (J)) then
+                           Vals (J) := New_Copy_Tree (Expression (Elmt));
+                           Rep_Count := Rep_Count + 1;
+
+                           --  Check for maximum others replication. Note that
+                           --  we skip this test if either of the restrictions
+                           --  No_Elaboration_Code or No_Implicit_Loops is
+                           --  active, or if this is a preelaborable unit.
+
+                           declare
+                              P : constant Entity_Id :=
+                                    Cunit_Entity (Current_Sem_Unit);
+
+                           begin
+                              if Restriction_Active (No_Elaboration_Code)
+                                or else Restriction_Active (No_Implicit_Loops)
+                                or else Is_Preelaborated (P)
+                                or else (Ekind (P) = E_Package_Body
+                                          and then
+                                            Is_Preelaborated (Spec_Entity (P)))
+                              then
+                                 null;
+
+                              elsif Rep_Count > Max_Others_Replicate then
+                                 return False;
+                              end if;
+                           end;
+                        end if;
+                     end loop;
+
+                     exit Component_Loop;
+
+                  --  Case of a subtype mark
+
+                  elsif Nkind (Choice) = N_Identifier
+                    and then Is_Type (Entity (Choice))
+                  then
+                     Lo := Type_Low_Bound  (Etype (Choice));
+                     Hi := Type_High_Bound (Etype (Choice));
+
+                  --  Case of subtype indication
+
+                  elsif Nkind (Choice) = N_Subtype_Indication then
+                     Lo := Low_Bound  (Range_Expression (Constraint (Choice)));
+                     Hi := High_Bound (Range_Expression (Constraint (Choice)));
+
+                  --  Case of a range
+
+                  elsif Nkind (Choice) = N_Range then
+                     Lo := Low_Bound (Choice);
+                     Hi := High_Bound (Choice);
+
+                  --  Normal subexpression case
+
+                  else pragma Assert (Nkind (Choice) in N_Subexpr);
+                     if not Compile_Time_Known_Value (Choice) then
+                        return False;
+
+                     else
+                        Vals (UI_To_Int (Expr_Value (Choice))) :=
+                          New_Copy_Tree (Expression (Elmt));
+                        goto Continue;
+                     end if;
+                  end if;
+
+                  --  Range cases merge with Lo,Hi said
+
+                  if not Compile_Time_Known_Value (Lo)
+                       or else
+                     not Compile_Time_Known_Value (Hi)
+                  then
+                     return False;
+                  else
+                     for J in UI_To_Int (Expr_Value (Lo)) ..
+                              UI_To_Int (Expr_Value (Hi))
+                     loop
+                        Vals (J) := New_Copy_Tree (Expression (Elmt));
+                     end loop;
+                  end if;
+
+               <<Continue>>
+                  Next (Choice);
+               end loop Choice_Loop;
+
+               Next (Elmt);
+            end loop Component_Loop;
+
+            --  If we get here the conversion is possible
+
+            Vlist := New_List;
+            for J in Vals'Range loop
+               Append (Vals (J), Vlist);
+            end loop;
+
+            Rewrite (N, Make_Aggregate (Loc, Expressions => Vlist));
+            Set_Aggregate_Bounds (N, Aggregate_Bounds (Original_Node (N)));
+            return True;
+         end;
+      end Flatten;
+
+      -------------
+      -- Is_Flat --
+      -------------
+
+      function Is_Flat (N : Node_Id; Dims : Int) return Boolean is
+         Elmt : Node_Id;
+
+      begin
+         if Dims = 0 then
+            return True;
+
+         elsif Nkind (N) = N_Aggregate then
+            if Present (Component_Associations (N)) then
+               return False;
+
+            else
+               Elmt := First (Expressions (N));
+
+               while Present (Elmt) loop
+                  if not Is_Flat (Elmt, Dims - 1) then
+                     return False;
+                  end if;
+
+                  Next (Elmt);
+               end loop;
+
+               return True;
+            end if;
+         else
+            return True;
+         end if;
+      end Is_Flat;
+
+   --  Start of processing for Convert_To_Positional
+
+   begin
+      --  Ada 2005 (AI-287): Do not convert in case of default initialized
+      --  components because in this case will need to call the corresponding
+      --  IP procedure.
+
+      if Has_Default_Init_Comps (N) then
+         return;
+      end if;
+
+      if Is_Flat (N, Number_Dimensions (Typ)) then
+         return;
+      end if;
+
+      if Is_Bit_Packed_Array (Typ)
+        and then not Handle_Bit_Packed
+      then
+         return;
+      end if;
+
+      --  Do not convert to positional if controlled components are
+      --  involved since these require special processing
+
+      if Has_Controlled_Component (Typ) then
+         return;
+      end if;
+
+      if Flatten (N, First_Index (Typ), First_Index (Base_Type (Typ))) then
+         Analyze_And_Resolve (N, Typ);
+      end if;
+   end Convert_To_Positional;
+
    ----------------------------
    -- Expand_Array_Aggregate --
    ----------------------------
@@ -2176,11 +2920,17 @@ package body Exp_Aggr is
    --         (c) For multidimensional arrays make sure that all subaggregates
    --             corresponding to the same dimension have the same bounds.
 
-   --  2. Check if the aggregate can be statically processed. If this is the
+   --  2. Check for packed array aggregate which can be converted to a
+   --     constant so that the aggregate disappeares completely.
+
+   --  3. Check case of nested aggregate. Generally nested aggregates are
+   --     handled during the processing of the parent aggregate.
+
+   --  4. Check if the aggregate can be statically processed. If this is the
    --     case pass it as is to Gigi. Note that a necessary condition for
    --     static processing is that the aggregate be fully positional.
 
-   --  3. If in place aggregate expansion is possible (i.e. no need to create
+   --  5. If in place aggregate expansion is possible (i.e. no need to create
    --     a temporary) then mark the aggregate as such and return. Otherwise
    --     create a new temporary and generate the appropriate initialization
    --     code.
@@ -2190,7 +2940,7 @@ package body Exp_Aggr is
 
       Typ  : constant Entity_Id := Etype (N);
       Ctyp : constant Entity_Id := Component_Type (Typ);
-      --  Typ is the correct constrained array subtype of the aggregate and
+      --  Typ is the correct constrained array subtype of the aggregate
       --  Ctyp is the corresponding component type.
 
       Aggr_Dimension : constant Pos := Number_Dimensions (Typ);
@@ -2208,10 +2958,10 @@ package body Exp_Aggr is
       --  is the expression in an assignment, assignment in place may be
       --  possible, provided other conditions are met on the LHS.
 
-      Others_Present : array (1 .. Aggr_Dimension) of Boolean
-        := (others => False);
-      --  If Others_Present (I) is True, then there is an others choice
-      --  in one of the sub-aggregates of N at dimension I.
+      Others_Present : array (1 .. Aggr_Dimension) of Boolean :=
+                         (others => False);
+      --  If Others_Present (J) is True, then there is an others choice
+      --  in one of the sub-aggregates of N at dimension J.
 
       procedure Build_Constrained_Type (Positional : Boolean);
       --  If the subtype is not static or unconstrained, build a constrained
@@ -2233,12 +2983,6 @@ package body Exp_Aggr is
       --  array sub-aggregate we start the computation from. Dim is the
       --  dimension corresponding to the sub-aggregate.
 
-      procedure Convert_To_Positional (N : Node_Id);
-      --  If possible, convert named notation to positional notation. This
-      --  conversion is possible only in some static cases. If the conversion
-      --  is possible, then N is rewritten with the analyzed converted
-      --  aggregate.
-
       function Has_Address_Clause (D : Node_Id) return Boolean;
       --  If the aggregate is the expression in an object declaration, it
       --  cannot be expanded in place. This function does a lookahead in the
@@ -2250,6 +2994,14 @@ package body Exp_Aggr is
       --  be done in place, because none of the new values can depend on the
       --  components of the target of the assignment.
 
+      function Must_Slide (N : Node_Id; Typ : Entity_Id) return Boolean;
+      --  A static aggregate in an object declaration can in most cases be
+      --  expanded in place. The one exception is when the aggregate is given
+      --  with component associations that specify different bounds from those
+      --  of the type definition in the object declaration. In this rather
+      --  pathological case the aggregate must slide, and we must introduce
+      --  an intermediate temporary to hold it.
+
       procedure Others_Check (Sub_Aggr : Node_Id; Dim : Pos);
       --  Checks that if an others choice is present in any sub-aggregate no
       --  aggregate index is outside the bounds of the index constraint.
@@ -2261,14 +3013,14 @@ package body Exp_Aggr is
       ----------------------------
 
       procedure Build_Constrained_Type (Positional : Boolean) is
-         Loc        : constant Source_Ptr := Sloc (N);
-         Agg_Type   : Entity_Id;
-         Comp       : Node_Id;
-         Decl       : Node_Id;
-         Typ        : constant Entity_Id := Etype (N);
-         Indices    : List_Id := New_List;
-         Num        : Int;
-         Sub_Agg    : Node_Id;
+         Loc      : constant Source_Ptr := Sloc (N);
+         Agg_Type : Entity_Id;
+         Comp     : Node_Id;
+         Decl     : Node_Id;
+         Typ      : constant Entity_Id := Etype (N);
+         Indices  : constant List_Id   := New_List;
+         Num      : Int;
+         Sub_Agg  : Node_Id;
 
       begin
          Agg_Type :=
@@ -2302,7 +3054,6 @@ package body Exp_Aggr is
             end loop;
 
          else
-
             --  We know the aggregate type is unconstrained and the
             --  aggregate is not processable by the back end, therefore
             --  not necessarily positional. Retrieve the bounds of each
@@ -2323,8 +3074,11 @@ package body Exp_Aggr is
                Type_Definition =>
                  Make_Constrained_Array_Definition (Loc,
                    Discrete_Subtype_Definitions => Indices,
-                   Subtype_Indication =>
-                     New_Occurrence_Of (Component_Type (Typ), Loc)));
+                   Component_Definition =>
+                     Make_Component_Definition (Loc,
+                       Aliased_Present => False,
+                       Subtype_Indication =>
+                         New_Occurrence_Of (Component_Type (Typ), Loc))));
 
          Insert_Action (N, Decl);
          Analyze (Decl);
@@ -2365,22 +3119,22 @@ package body Exp_Aggr is
          elsif Aggr_Hi = Ind_Hi then
             Cond :=
               Make_Op_Lt (Loc,
-                Left_Opnd  => Duplicate_Subexpr (Aggr_Lo),
-                Right_Opnd => Duplicate_Subexpr (Ind_Lo));
+                Left_Opnd  => Duplicate_Subexpr_Move_Checks (Aggr_Lo),
+                Right_Opnd => Duplicate_Subexpr_Move_Checks (Ind_Lo));
 
          elsif Aggr_Lo = Ind_Lo then
             Cond :=
               Make_Op_Gt (Loc,
-                Left_Opnd  => Duplicate_Subexpr (Aggr_Hi),
-                Right_Opnd => Duplicate_Subexpr (Ind_Hi));
+                Left_Opnd  => Duplicate_Subexpr_Move_Checks (Aggr_Hi),
+                Right_Opnd => Duplicate_Subexpr_Move_Checks (Ind_Hi));
 
          else
             Cond :=
               Make_Or_Else (Loc,
                 Left_Opnd =>
                   Make_Op_Lt (Loc,
-                    Left_Opnd  => Duplicate_Subexpr (Aggr_Lo),
-                    Right_Opnd => Duplicate_Subexpr (Ind_Lo)),
+                    Left_Opnd  => Duplicate_Subexpr_Move_Checks (Aggr_Lo),
+                    Right_Opnd => Duplicate_Subexpr_Move_Checks (Ind_Lo)),
 
                 Right_Opnd =>
                   Make_Op_Gt (Loc,
@@ -2393,15 +3147,17 @@ package body Exp_Aggr is
               Make_And_Then (Loc,
                 Left_Opnd =>
                   Make_Op_Le (Loc,
-                    Left_Opnd  => Duplicate_Subexpr (Aggr_Lo),
-                    Right_Opnd => Duplicate_Subexpr (Aggr_Hi)),
+                    Left_Opnd  => Duplicate_Subexpr_Move_Checks (Aggr_Lo),
+                    Right_Opnd => Duplicate_Subexpr_Move_Checks (Aggr_Hi)),
 
                 Right_Opnd => Cond);
 
             Set_Analyzed (Left_Opnd  (Left_Opnd (Cond)), False);
             Set_Analyzed (Right_Opnd (Left_Opnd (Cond)), False);
             Insert_Action (N,
-              Make_Raise_Constraint_Error (Loc, Condition => Cond));
+              Make_Raise_Constraint_Error (Loc,
+                Condition => Cond,
+                Reason    => CE_Length_Check_Failed));
          end if;
       end Check_Bounds;
 
@@ -2421,10 +3177,10 @@ package body Exp_Aggr is
          Ind_Typ : constant Entity_Id := Aggr_Index_Typ (Dim);
          --  The index type for this dimension.
 
-         Cond : Node_Id := Empty;
+         Cond  : Node_Id := Empty;
 
-         Assoc  : Node_Id;
-         Expr   : Node_Id;
+         Assoc : Node_Id;
+         Expr  : Node_Id;
 
       begin
          --  If index checks are on generate the test
@@ -2448,22 +3204,22 @@ package body Exp_Aggr is
          elsif Aggr_Hi = Sub_Hi then
             Cond :=
               Make_Op_Ne (Loc,
-                Left_Opnd  => Duplicate_Subexpr (Aggr_Lo),
-                Right_Opnd => Duplicate_Subexpr (Sub_Lo));
+                Left_Opnd  => Duplicate_Subexpr_Move_Checks (Aggr_Lo),
+                Right_Opnd => Duplicate_Subexpr_Move_Checks (Sub_Lo));
 
          elsif Aggr_Lo = Sub_Lo then
             Cond :=
               Make_Op_Ne (Loc,
-                Left_Opnd  => Duplicate_Subexpr (Aggr_Hi),
-                Right_Opnd => Duplicate_Subexpr (Sub_Hi));
+                Left_Opnd  => Duplicate_Subexpr_Move_Checks (Aggr_Hi),
+                Right_Opnd => Duplicate_Subexpr_Move_Checks (Sub_Hi));
 
          else
             Cond :=
               Make_Or_Else (Loc,
                 Left_Opnd =>
                   Make_Op_Ne (Loc,
-                    Left_Opnd  => Duplicate_Subexpr (Aggr_Lo),
-                    Right_Opnd => Duplicate_Subexpr (Sub_Lo)),
+                    Left_Opnd  => Duplicate_Subexpr_Move_Checks (Aggr_Lo),
+                    Right_Opnd => Duplicate_Subexpr_Move_Checks (Sub_Lo)),
 
                 Right_Opnd =>
                   Make_Op_Ne (Loc,
@@ -2473,7 +3229,9 @@ package body Exp_Aggr is
 
          if Present (Cond) then
             Insert_Action (N,
-              Make_Raise_Constraint_Error (Loc, Condition => Cond));
+              Make_Raise_Constraint_Error (Loc,
+                Condition => Cond,
+                Reason    => CE_Length_Check_Failed));
          end if;
 
          --  Now look inside the sub-aggregate to see if there is more work
@@ -2508,12 +3266,13 @@ package body Exp_Aggr is
       ----------------------------
 
       procedure Compute_Others_Present (Sub_Aggr : Node_Id; Dim : Pos) is
-         Assoc  : Node_Id;
-         Expr   : Node_Id;
+         Assoc : Node_Id;
+         Expr  : Node_Id;
 
       begin
          if Present (Component_Associations (Sub_Aggr)) then
             Assoc := Last (Component_Associations (Sub_Aggr));
+
             if Nkind (First (Choices (Assoc))) = N_Others_Choice then
                Others_Present (Dim) := True;
             end if;
@@ -2546,235 +3305,16 @@ package body Exp_Aggr is
          end if;
       end Compute_Others_Present;
 
-      ---------------------------
-      -- Convert_To_Positional --
-      ---------------------------
-
-      procedure Convert_To_Positional (N : Node_Id) is
-         Typ  : constant Entity_Id := Etype (N);
-         Ndim : constant Pos       := Number_Dimensions (Typ);
-         Xtyp : constant Entity_Id := Etype (First_Index (Typ));
-         Blo  : constant Node_Id   :=
-                  Type_Low_Bound (Etype (First_Index (Base_Type (Typ))));
-         Lo   : constant Node_Id   := Type_Low_Bound (Xtyp);
-         Hi   : constant Node_Id   := Type_High_Bound (Xtyp);
-         Lov  : Uint;
-         Hiv  : Uint;
-
-         Max_Aggr_Size : constant := 500;
-         --  Maximum size of aggregate produced by converting positional to
-         --  named notation. This avoids running away with attempts to
-         --  convert huge aggregates.
-
-         Max_Others_Replicate : constant := 5;
-         --  This constant defines the maximum expansion of an others clause
-         --  into a list of values. This applies when converting a named
-         --  aggregate to positional form for processing by the back end.
-         --  If a given others clause generates more than five values, the
-         --  aggregate is retained as named, since the loop is more compact.
-         --  However, this constant is completely overridden if restriction
-         --  No_Elaboration_Code is active, since in this case, the loop
-         --  would not be allowed anyway. Similarly No_Implicit_Loops causes
-         --  this parameter to be ignored.
-
-      begin
-         --  For now, we only handle the one dimensional case and aggregates
-         --  that are not part of a component_association
-
-         if Ndim > 1 or else Nkind (Parent (N)) = N_Aggregate
-           or else Nkind (Parent (N)) = N_Component_Association
-         then
-            return;
-         end if;
-
-         --  If already positional, nothing to do!
-
-         if No (Component_Associations (N)) then
-            return;
-         end if;
-
-         --  Bounds need to be known at compile time
-
-         if not Compile_Time_Known_Value (Lo)
-           or else not Compile_Time_Known_Value (Hi)
-         then
-            return;
-         end if;
-
-         --  Do not attempt to convert bit packed arrays, since they cannot
-         --  be handled by the backend in any case.
-
-         if Is_Bit_Packed_Array (Typ) then
-            return;
-         end if;
-
-         --  Do not convert to positional if controlled components are
-         --  involved since these require special processing
-
-         if Has_Controlled_Component (Typ) then
-            return;
-         end if;
-
-         --  Get bounds and check reasonable size (positive, not too large)
-         --  Also only handle bounds starting at the base type low bound for
-         --  now since the compiler isn't able to handle different low bounds
-         --  yet
-
-         Lov := Expr_Value (Lo);
-         Hiv := Expr_Value (Hi);
-
-         if Hiv < Lov
-           or else (Hiv - Lov > Max_Aggr_Size)
-           or else not Compile_Time_Known_Value (Blo)
-           or else (Lov /= Expr_Value (Blo))
-         then
-            return;
-         end if;
-
-         --  Bounds must be in integer range (for array Vals below)
-
-         if not UI_Is_In_Int_Range (Lov)
-             or else
-            not UI_Is_In_Int_Range (Hiv)
-         then
-            return;
-         end if;
-
-         --  Determine if set of alternatives is suitable for conversion
-         --  and build an array containing the values in sequence.
-
-         declare
-            Vals : array (UI_To_Int (Lov) .. UI_To_Int (Hiv))
-                     of Node_Id := (others => Empty);
-            --  The values in the aggregate sorted appropriately
-
-            Vlist : List_Id;
-            --  Same data as Vals in list form
-
-            Rep_Count : Nat;
-            --  Used to validate Max_Others_Replicate limit
-
-            Elmt   : Node_Id;
-            Num    : Int := UI_To_Int (Lov);
-            Choice : Node_Id;
-            Lo, Hi : Node_Id;
-
-         begin
-            if Present (Expressions (N)) then
-               Elmt := First (Expressions (N));
-               while Present (Elmt) loop
-                  Vals (Num) := Relocate_Node (Elmt);
-                  Num := Num + 1;
-                  Next (Elmt);
-               end loop;
-            end if;
-
-            Elmt := First (Component_Associations (N));
-            Component_Loop : while Present (Elmt) loop
-
-               Choice := First (Choices (Elmt));
-               Choice_Loop : while Present (Choice) loop
-
-                  --  If we have an others choice, fill in the missing elements
-                  --  subject to the limit established by Max_Others_Replicate.
-
-                  if Nkind (Choice) = N_Others_Choice then
-                     Rep_Count := 0;
-
-                     for J in Vals'Range loop
-                        if No (Vals (J)) then
-                           Vals (J) := New_Copy_Tree (Expression (Elmt));
-                           Rep_Count := Rep_Count + 1;
-
-                           if Rep_Count > Max_Others_Replicate
-                             and then not Restrictions (No_Elaboration_Code)
-                             and then not Restrictions (No_Implicit_Loops)
-                           then
-                              return;
-                           end if;
-                        end if;
-                     end loop;
-
-                     exit Component_Loop;
-
-                  --  Case of a subtype mark
-
-                  elsif (Nkind (Choice) = N_Identifier
-                          and then Is_Type (Entity (Choice)))
-                  then
-                     Lo := Type_Low_Bound  (Etype (Choice));
-                     Hi := Type_High_Bound (Etype (Choice));
-
-                  --  Case of subtype indication
-
-                  elsif Nkind (Choice) = N_Subtype_Indication then
-                     Lo := Low_Bound  (Range_Expression (Constraint (Choice)));
-                     Hi := High_Bound (Range_Expression (Constraint (Choice)));
-
-                  --  Case of a range
-
-                  elsif Nkind (Choice) = N_Range then
-                     Lo := Low_Bound (Choice);
-                     Hi := High_Bound (Choice);
-
-                  --  Normal subexpression case
-
-                  else pragma Assert (Nkind (Choice) in N_Subexpr);
-                     if not Compile_Time_Known_Value (Choice) then
-                        return;
-
-                     else
-                        Vals (UI_To_Int (Expr_Value (Choice))) :=
-                          New_Copy_Tree (Expression (Elmt));
-                        goto Continue;
-                     end if;
-                  end if;
-
-                  --  Range cases merge with Lo,Hi said
-
-                  if not Compile_Time_Known_Value (Lo)
-                       or else
-                     not Compile_Time_Known_Value (Hi)
-                  then
-                     return;
-                  else
-                     for J in UI_To_Int (Expr_Value (Lo)) ..
-                              UI_To_Int (Expr_Value (Hi))
-                     loop
-                        Vals (J) := New_Copy_Tree (Expression (Elmt));
-                     end loop;
-                  end if;
-
-               <<Continue>>
-                  Next (Choice);
-               end loop Choice_Loop;
-
-               Next (Elmt);
-            end loop Component_Loop;
-
-            --  If we get here the conversion is possible
-
-            Vlist := New_List;
-            for J in Vals'Range loop
-               Append (Vals (J), Vlist);
-            end loop;
-
-            Rewrite (N, Make_Aggregate (Loc, Expressions => Vlist));
-            Analyze_And_Resolve (N, Typ);
-         end;
-      end Convert_To_Positional;
-
-      -------------------------
-      --  Has_Address_Clause --
-      -------------------------
+      ------------------------
+      -- Has_Address_Clause --
+      ------------------------
 
       function Has_Address_Clause (D : Node_Id) return Boolean is
-         Id   : Entity_Id := Defining_Identifier (D);
+         Id   : constant Entity_Id := Defining_Identifier (D);
          Decl : Node_Id := Next (D);
 
       begin
          while Present (Decl) loop
-
             if Nkind (Decl) = N_At_Clause
                and then Chars (Identifier (Decl)) = Chars (Id)
             then
@@ -2805,6 +3345,10 @@ package body Exp_Aggr is
          Obj_Lo  : Node_Id;
          Obj_Hi  : Node_Id;
 
+         function Is_Others_Aggregate (Aggr : Node_Id) return Boolean;
+         --   Aggregates that consist of a single Others choice are safe
+         --  if the single expression is.
+
          function Safe_Aggregate (Aggr : Node_Id) return Boolean;
          --  Check recursively that each component of a (sub)aggregate does
          --  not depend on the variable being assigned to.
@@ -2813,6 +3357,18 @@ package body Exp_Aggr is
          --  Verify that an expression cannot depend on the variable being
          --  assigned to. Room for improvement here (but less than before).
 
+         -------------------------
+         -- Is_Others_Aggregate --
+         -------------------------
+
+         function Is_Others_Aggregate (Aggr : Node_Id) return Boolean is
+         begin
+            return No (Expressions (Aggr))
+              and then Nkind
+                (First (Choices (First (Component_Associations (Aggr)))))
+                  = N_Others_Choice;
+         end Is_Others_Aggregate;
+
          --------------------
          -- Safe_Aggregate --
          --------------------
@@ -2868,6 +3424,10 @@ package body Exp_Aggr is
             function Check_Component (Comp : Node_Id) return Boolean;
             --  Do the recursive traversal, after copy.
 
+            ---------------------
+            -- Check_Component --
+            ---------------------
+
             function Check_Component (Comp : Node_Id) return Boolean is
             begin
                if Is_Overloaded (Comp) then
@@ -2894,7 +3454,7 @@ package body Exp_Aggr is
                            and then Check_Component (Prefix (Comp)));
             end Check_Component;
 
-            --  Start of processing for Safe_Component
+         --  Start of processing for Safe_Component
 
          begin
             --  If the component appears in an association that may
@@ -2907,13 +3467,28 @@ package body Exp_Aggr is
             if not Analyzed (Comp) then
                if Is_Overloaded (Expr) then
                   return False;
+
+               elsif Nkind (Expr) = N_Aggregate
+                  and then not Is_Others_Aggregate (Expr)
+               then
+                  return False;
+
+               elsif Nkind (Expr) = N_Allocator then
+                  --  For now, too complex to analyze.
+
+                  return False;
                end if;
 
                Comp := New_Copy_Tree (Expr);
+               Set_Parent (Comp, Parent (Expr));
                Analyze (Comp);
             end if;
 
-            return Check_Component (Comp);
+            if Nkind (Comp) = N_Aggregate then
+               return Safe_Aggregate (Comp);
+            else
+               return Check_Component (Comp);
+            end if;
          end Safe_Component;
 
       --  Start of processing for In_Place_Assign_OK
@@ -2929,11 +3504,7 @@ package body Exp_Aggr is
             --  are derived from the left-hand side, and the assignment is
             --  safe if the expression is.
 
-            if No (Expressions (N))
-              and then Nkind
-                (First (Choices (First (Component_Associations (N)))))
-                  = N_Others_Choice
-            then
+            if Is_Others_Aggregate (N) then
                return
                  Safe_Component
                   (Expression (First (Component_Associations (N))));
@@ -2961,10 +3532,54 @@ package body Exp_Aggr is
             end loop;
          end if;
 
-         --  Now check the component values themselves.
+         --  Now check the component values themselves.
+
+         return Safe_Aggregate (N);
+      end In_Place_Assign_OK;
+
+      ----------------
+      -- Must_Slide --
+      ----------------
+
+      function Must_Slide (N : Node_Id; Typ : Entity_Id) return Boolean
+      is
+         Obj_Type : constant Entity_Id :=
+                      Etype (Defining_Identifier (Parent (N)));
+
+         L1, L2, H1, H2 : Node_Id;
+
+      begin
+         --  No sliding if the type of the object is not established yet, if
+         --  it is an unconstrained type whose actual subtype comes from the
+         --  aggregate, or if the two types are identical.
+
+         if not Is_Array_Type (Obj_Type) then
+            return False;
+
+         elsif not Is_Constrained (Obj_Type) then
+            return False;
+
+         elsif Typ = Obj_Type then
+            return False;
+
+         else
+            --  Sliding can only occur along the first dimension
 
-         return Safe_Aggregate (N);
-      end In_Place_Assign_OK;
+            Get_Index_Bounds (First_Index (Typ), L1, H1);
+            Get_Index_Bounds (First_Index (Obj_Type), L2, H2);
+
+            if not Is_Static_Expression (L1)
+              or else not Is_Static_Expression (L2)
+              or else not Is_Static_Expression (H1)
+              or else not Is_Static_Expression (H2)
+            then
+               return False;
+            else
+               return Expr_Value (L1) /= Expr_Value (L2)
+                 or else Expr_Value (H1) /= Expr_Value (H2);
+            end if;
+         end if;
+      end Must_Slide;
 
       ------------------
       -- Others_Check --
@@ -3041,7 +3656,7 @@ package body Exp_Aggr is
          end if;
 
          --  If we are dealing with a positional sub-aggregate with an
-         --  others choice compute the number or positional elements.
+         --  others choice then compute the number or positional elements.
 
          if Need_To_Check and then Present (Expressions (Sub_Aggr)) then
             Expr := First (Expressions (Sub_Aggr));
@@ -3056,10 +3671,11 @@ package body Exp_Aggr is
 
          elsif Need_To_Check then
             Compute_Choices_Lo_And_Choices_Hi : declare
+
                Table : Case_Table_Type (1 .. Nb_Choices);
                --  Used to sort all the different choice values
 
-               I    : Pos := 1;
+               J    : Pos := 1;
                Low  : Node_Id;
                High : Node_Id;
 
@@ -3073,10 +3689,10 @@ package body Exp_Aggr is
                      end if;
 
                      Get_Index_Bounds (Choice, Low, High);
-                     Table (I).Choice_Lo := Low;
-                     Table (I).Choice_Hi := High;
+                     Table (J).Choice_Lo := Low;
+                     Table (J).Choice_Hi := High;
 
-                     I := I + 1;
+                     J := J + 1;
                      Next (Choice);
                   end loop;
 
@@ -3117,14 +3733,16 @@ package body Exp_Aggr is
                         Prefix         => New_Reference_To (Ind_Typ, Loc),
                         Attribute_Name => Name_Pos,
                         Expressions    =>
-                          New_List (Duplicate_Subexpr (Aggr_Lo))),
+                          New_List
+                            (Duplicate_Subexpr_Move_Checks (Aggr_Lo))),
                     Right_Opnd => Make_Integer_Literal (Loc, Nb_Elements - 1)),
 
                 Right_Opnd =>
                   Make_Attribute_Reference (Loc,
                     Prefix         => New_Reference_To (Ind_Typ, Loc),
                     Attribute_Name => Name_Pos,
-                    Expressions    => New_List (Duplicate_Subexpr (Aggr_Hi))));
+                    Expressions    => New_List (
+                      Duplicate_Subexpr_Move_Checks (Aggr_Hi))));
 
          --  If we are dealing with an aggregate containing an others
          --  choice and discrete choices we generate the following test:
@@ -3137,18 +3755,24 @@ package body Exp_Aggr is
               Make_Or_Else (Loc,
                 Left_Opnd =>
                   Make_Op_Lt (Loc,
-                    Left_Opnd  => Duplicate_Subexpr (Choices_Lo),
-                    Right_Opnd => Duplicate_Subexpr (Aggr_Lo)),
+                    Left_Opnd  =>
+                      Duplicate_Subexpr_Move_Checks (Choices_Lo),
+                    Right_Opnd =>
+                      Duplicate_Subexpr_Move_Checks (Aggr_Lo)),
 
                 Right_Opnd =>
                   Make_Op_Gt (Loc,
-                    Left_Opnd  => Duplicate_Subexpr (Choices_Hi),
-                    Right_Opnd => Duplicate_Subexpr (Aggr_Hi)));
+                    Left_Opnd  =>
+                      Duplicate_Subexpr (Choices_Hi),
+                    Right_Opnd =>
+                      Duplicate_Subexpr (Aggr_Hi)));
          end if;
 
          if Present (Cond) then
             Insert_Action (N,
-              Make_Raise_Constraint_Error (Loc, Condition => Cond));
+              Make_Raise_Constraint_Error (Loc,
+                Condition => Cond,
+                Reason    => CE_Length_Check_Failed));
          end if;
 
          --  Now look inside the sub-aggregate to see if there is more work
@@ -3181,10 +3805,10 @@ package body Exp_Aggr is
       --  Remaining Expand_Array_Aggregate variables
 
       Tmp : Entity_Id;
-      --  Holds the temporary aggregate value.
+      --  Holds the temporary aggregate value
 
       Tmp_Decl : Node_Id;
-      --  Holds the declaration of Tmp.
+      --  Holds the declaration of Tmp
 
       Aggr_Code   : List_Id;
       Parent_Node : Node_Id;
@@ -3201,14 +3825,17 @@ package body Exp_Aggr is
          return;
       end if;
 
-      --  If during semantic analysis it has been determined that aggregate N
-      --  will raise Constraint_Error at run-time, then the aggregate node
-      --  has been replaced with an N_Raise_Constraint_Error node and we
-      --  should never get here.
+      --  If the semantic analyzer has determined that aggregate N will raise
+      --  Constraint_Error at run-time, then the aggregate node has been
+      --  replaced with an N_Raise_Constraint_Error node and we should
+      --  never get here.
 
       pragma Assert (not Raises_Constraint_Error (N));
 
-      --  STEP 1: Check (a)
+      --  STEP 1a.
+
+      --  Check that the index range defined by aggregate bounds is
+      --  compatible with corresponding index subtype.
 
       Index_Compatibility_Check : declare
          Aggr_Index_Range : Node_Id := First_Index (Typ);
@@ -3253,11 +3880,17 @@ package body Exp_Aggr is
          end loop;
       end Index_Compatibility_Check;
 
-      --  STEP 1: Check (b)
+      --  STEP 1b.
+
+      --  If an others choice is present check that no aggregate
+      --  index is outside the bounds of the index constraint.
 
       Others_Check (N, 1);
 
-      --  STEP 1: Check (c)
+      --  STEP 1c.
+
+      --  For multidimensional arrays make sure that all subaggregates
+      --  corresponding to the same dimension have the same bounds.
 
       if Aggr_Dimension > 1 then
          Check_Same_Aggr_Bounds (N, 1);
@@ -3265,23 +3898,37 @@ package body Exp_Aggr is
 
       --  STEP 2.
 
-      --  First try to convert to positional form. If the result is not
-      --  an aggregate any more, then we are done with the analysis (it
-      --  it could be a string literal or an identifier for a temporary
-      --  variable following this call). If result is an analyzed aggregate
-      --  the transformation was also successful and we are done as well.
+      --  Here we test for is packed array aggregate that we can handle
+      --  at compile time. If so, return with transformation done. Note
+      --  that we do this even if the aggregate is nested, because once
+      --  we have done this processing, there is no more nested aggregate!
+
+      if Packed_Array_Aggregate_Handled (N) then
+         return;
+      end if;
+
+      --  At this point we try to convert to positional form
 
       Convert_To_Positional (N);
 
+      --  if the result is no longer an aggregate (e.g. it may be a string
+      --  literal, or a temporary which has the needed value), then we are
+      --  done, since there is no longer a nested aggregate.
+
       if Nkind (N) /= N_Aggregate then
          return;
 
+      --  We are also done if the result is an analyzed aggregate
+      --  This case could use more comments ???
+
       elsif Analyzed (N)
         and then N /= Original_Node (N)
       then
          return;
       end if;
 
+      --  Now see if back end processing is possible
+
       if Backend_Processing_Possible (N) then
 
          --  If the aggregate is static but the constraints are not, build
@@ -3316,6 +3963,8 @@ package body Exp_Aggr is
          return;
       end if;
 
+      --  STEP 3.
+
       --  Delay expansion for nested aggregates it will be taken care of
       --  when the parent aggregate is expanded
 
@@ -3339,7 +3988,7 @@ package body Exp_Aggr is
          return;
       end if;
 
-      --  STEP 3.
+      --  STEP 4.
 
       --  Look if in place aggregate expansion is possible
 
@@ -3356,21 +4005,26 @@ package body Exp_Aggr is
            (N, Sec_Stack => Has_Controlled_Component (Typ));
       end if;
 
-      Maybe_In_Place_OK :=
-        Comes_From_Source (N)
-          and then Nkind (Parent (N)) = N_Assignment_Statement
-          and then not Is_Bit_Packed_Array (Typ)
-          and then not Has_Controlled_Component (Typ)
-          and then In_Place_Assign_OK;
+      if Has_Default_Init_Comps (N) then
+         Maybe_In_Place_OK := False;
+      else
+         Maybe_In_Place_OK :=
+           Comes_From_Source (N)
+             and then Nkind (Parent (N)) = N_Assignment_Statement
+             and then not Is_Bit_Packed_Array (Typ)
+             and then not Has_Controlled_Component (Typ)
+             and then In_Place_Assign_OK;
+      end if;
 
-      if Comes_From_Source (Parent (N))
+      if not Has_Default_Init_Comps (N)
+         and then Comes_From_Source (Parent (N))
          and then Nkind (Parent (N)) = N_Object_Declaration
+         and then not Must_Slide (N, Typ)
          and then N = Expression (Parent (N))
          and then not Is_Bit_Packed_Array (Typ)
          and then not Has_Controlled_Component (Typ)
          and then not Has_Address_Clause (Parent (N))
       then
-
          Tmp := Defining_Identifier (Parent (N));
          Set_No_Initialization (Parent (N));
          Set_Expression (Parent (N), Empty);
@@ -3399,17 +4053,39 @@ package body Exp_Aggr is
 
          if Etype (Tmp) /= Etype (N) then
             Apply_Length_Check (N, Etype (Tmp));
+
+            if Nkind (N) = N_Raise_Constraint_Error then
+
+               --  Static error, nothing further to expand
+
+               return;
+            end if;
+         end if;
+
+      elsif Maybe_In_Place_OK
+        and then Nkind (Name (Parent (N))) = N_Explicit_Dereference
+        and then Is_Entity_Name (Prefix (Name (Parent (N))))
+      then
+         Tmp := Name (Parent (N));
+
+         if Etype (Tmp) /= Etype (N) then
+            Apply_Length_Check (N, Etype (Tmp));
          end if;
 
       elsif Maybe_In_Place_OK
         and then Nkind (Name (Parent (N))) = N_Slice
-        and then Safe_Slice_Assignment (N, Typ)
+        and then Safe_Slice_Assignment (N)
       then
-         --  Safe_Slice_Assignment rewrites assignment as a loop.
+         --  Safe_Slice_Assignment rewrites assignment as a loop
 
          return;
 
+      --  Step 5
+
+      --  In place aggregate expansion is not possible
+
       else
+         Maybe_In_Place_OK := False;
          Tmp := Make_Defining_Identifier (Loc, New_Internal_Name ('A'));
          Tmp_Decl :=
            Make_Object_Declaration
@@ -3437,11 +4113,34 @@ package body Exp_Aggr is
       --  index checks because this code is guaranteed not to raise CE
       --  on index checks. However we should *not* suppress all checks.
 
-      Aggr_Code :=
-        Build_Array_Aggr_Code (N,
-          Index       => First_Index (Typ),
-          Into        => New_Reference_To (Tmp, Loc),
-          Scalar_Comp => Is_Scalar_Type (Ctyp));
+      declare
+         Target : Node_Id;
+
+      begin
+         if Nkind (Tmp) = N_Defining_Identifier then
+            Target := New_Reference_To (Tmp, Loc);
+
+         else
+
+            if Has_Default_Init_Comps (N) then
+
+               --  Ada 2005 (AI-287): This case has not been analyzed???
+
+               raise Program_Error;
+            end if;
+
+            --  Name in assignment is explicit dereference
+
+            Target := New_Copy (Tmp);
+         end if;
+
+         Aggr_Code :=
+           Build_Array_Aggr_Code (N,
+             Ctype       => Ctyp,
+             Index       => First_Index (Typ),
+             Into        => Target,
+             Scalar_Comp => Is_Scalar_Type (Ctyp));
+      end;
 
       if Comes_From_Source (Tmp) then
          Insert_Actions_After (Parent (N), Aggr_Code);
@@ -3450,12 +4149,13 @@ package body Exp_Aggr is
          Insert_Actions (N, Aggr_Code);
       end if;
 
+      --  If the aggregate has been assigned in place, remove the original
+      --  assignment.
+
       if Nkind (Parent (N)) = N_Assignment_Statement
-        and then Is_Entity_Name (Name (Parent (N)))
-        and then Tmp = Entity (Name (Parent (N)))
+        and then Maybe_In_Place_OK
       then
          Rewrite (Parent (N), Make_Null_Statement (Loc));
-         Analyze (N);
 
       elsif Nkind (Parent (N)) /= N_Object_Declaration
         or else Tmp /= Defining_Identifier (Parent (N))
@@ -3476,6 +4176,10 @@ package body Exp_Aggr is
       else
          Expand_Array_Aggregate (N);
       end if;
+
+   exception
+      when RE_Not_Available =>
+         return;
    end Expand_N_Aggregate;
 
    ----------------------------------
@@ -3495,7 +4199,7 @@ package body Exp_Aggr is
       Typ : constant Entity_Id  := Etype (N);
 
    begin
-      --  If the ancestor is a subtype mark, an init_proc must be called
+      --  If the ancestor is a subtype mark, an init proc must be called
       --  on the resulting object which thus has to be materialized in
       --  the front-end
 
@@ -3522,6 +4226,10 @@ package body Exp_Aggr is
               Parent_Expr => A);
          end if;
       end if;
+
+   exception
+      when RE_Not_Available =>
+         return;
    end Expand_N_Extension_Aggregate;
 
    -----------------------------
@@ -3533,10 +4241,10 @@ package body Exp_Aggr is
       Orig_Tag    : Node_Id := Empty;
       Parent_Expr : Node_Id := Empty)
    is
-      Loc   : constant Source_Ptr   := Sloc  (N);
-      Comps : constant List_Id      := Component_Associations (N);
-      Typ   : constant Entity_Id    := Etype (N);
-      Base_Typ : constant Entity_Id := Base_Type (Typ);
+      Loc      : constant Source_Ptr := Sloc  (N);
+      Comps    : constant List_Id    := Component_Associations (N);
+      Typ      : constant Entity_Id  := Etype (N);
+      Base_Typ : constant Entity_Id  := Base_Type (Typ);
 
       function Has_Delayed_Nested_Aggregate_Or_Tagged_Comps return Boolean;
       --  Checks the presence of a nested aggregate which needs Late_Expansion
@@ -3547,7 +4255,7 @@ package body Exp_Aggr is
       --------------------------------------------------
 
       function Has_Delayed_Nested_Aggregate_Or_Tagged_Comps return Boolean is
-         C     : Node_Id;
+         C      : Node_Id;
          Expr_Q : Node_Id;
 
       begin
@@ -3557,7 +4265,6 @@ package body Exp_Aggr is
 
          C := First (Comps);
          while Present (C) loop
-
             if Nkind (Expression (C)) = N_Qualified_Expression then
                Expr_Q := Expression (Expression (C));
             else
@@ -3589,7 +4296,7 @@ package body Exp_Aggr is
          end loop;
 
          return False;
-      end  Has_Delayed_Nested_Aggregate_Or_Tagged_Comps;
+      end Has_Delayed_Nested_Aggregate_Or_Tagged_Comps;
 
       --  Remaining Expand_Record_Aggregate variables
 
@@ -3600,6 +4307,21 @@ package body Exp_Aggr is
    --  Start of processing for Expand_Record_Aggregate
 
    begin
+      --  If the aggregate is to be assigned to an atomic variable, we
+      --  have to prevent a piecemeal assignment even if the aggregate
+      --  is to be expanded. We create a temporary for the aggregate, and
+      --  assign the temporary instead, so that the back end can generate
+      --  an atomic move for it.
+
+      if Is_Atomic (Typ)
+        and then (Nkind (Parent (N)) = N_Object_Declaration
+                    or else Nkind (Parent (N)) = N_Assignment_Statement)
+        and then Comes_From_Source (Parent (N))
+      then
+         Expand_Atomic_Aggregate (N, Typ);
+         return;
+      end if;
+
       --  Gigi doesn't handle properly temporaries of variable size
       --  so we generate it in the front-end
 
@@ -3615,6 +4337,12 @@ package body Exp_Aggr is
       then
          Convert_To_Assignments (N, Typ);
 
+         --  Ada 2005 (AI-287): In case of default initialized components we
+         --  convert the aggregate into assignments.
+
+      elsif Has_Default_Init_Comps (N) then
+         Convert_To_Assignments (N, Typ);
+
       elsif Has_Delayed_Nested_Aggregate_Or_Tagged_Comps then
          Convert_To_Assignments (N, Typ);
 
@@ -3630,26 +4358,86 @@ package body Exp_Aggr is
       elsif Is_Tagged_Type (Typ) and then Has_Discriminants (Typ) then
          Convert_To_Assignments (N, Typ);
 
+      --  If some components are mutable, the size of the aggregate component
+      --  may be disctinct from the default size of the type component, so
+      --  we need to expand to insure that the back-end copies the proper
+      --  size of the data.
+
+      elsif Has_Mutable_Components (Typ) then
+         Convert_To_Assignments (N, Typ);
+
+      --  If the type involved has any non-bit aligned components, then
+      --  we are not sure that the back end can handle this case correctly.
+
+      elsif Type_May_Have_Bit_Aligned_Components (Typ) then
+         Convert_To_Assignments (N, Typ);
+
       --  In all other cases we generate a proper aggregate that
       --  can be handled by gigi.
 
       else
-         if not Has_Discriminants (Typ) then
-
-            --  This bizarre if/elsif is to avoid a compiler crash ???
+         --  If no discriminants, nothing special to do
 
+         if not Has_Discriminants (Typ) then
             null;
 
+         --  Case of discriminants present
+
          elsif Is_Derived_Type (Typ) then
 
-            --  Non-girder discriminants are replaced with girder discriminants
+            --  For untagged types,  non-stored discriminants are replaced
+            --  with stored discriminants, which are the ones that gigi uses
+            --  to describe the type and its components.
 
-            declare
+            Generate_Aggregate_For_Derived_Type : declare
+               Constraints  : constant List_Id := New_List;
                First_Comp   : Node_Id;
                Discriminant : Entity_Id;
+               Decl         : Node_Id;
+               Num_Disc     : Int := 0;
+               Num_Gird     : Int := 0;
+
+               procedure Prepend_Stored_Values (T : Entity_Id);
+               --  Scan the list of stored discriminants of the type, and
+               --  add their values to the aggregate being built.
+
+               ---------------------------
+               -- Prepend_Stored_Values --
+               ---------------------------
+
+               procedure Prepend_Stored_Values (T : Entity_Id) is
+               begin
+                  Discriminant := First_Stored_Discriminant (T);
+
+                  while Present (Discriminant) loop
+                     New_Comp :=
+                       Make_Component_Association (Loc,
+                         Choices    =>
+                           New_List (New_Occurrence_Of (Discriminant, Loc)),
+
+                         Expression =>
+                           New_Copy_Tree (
+                             Get_Discriminant_Value (
+                                 Discriminant,
+                                 Typ,
+                                 Discriminant_Constraint (Typ))));
+
+                     if No (First_Comp) then
+                        Prepend_To (Component_Associations (N), New_Comp);
+                     else
+                        Insert_After (First_Comp, New_Comp);
+                     end if;
+
+                     First_Comp := New_Comp;
+                     Next_Stored_Discriminant (Discriminant);
+                  end loop;
+               end Prepend_Stored_Values;
+
+            --  Start of processing for Generate_Aggregate_For_Derived_Type
 
             begin
-               --  Remove all the discriminants
+               --  Remove the associations for the  discriminant of
+               --  the derived type.
 
                First_Comp := First (Component_Associations (N));
 
@@ -3661,37 +4449,79 @@ package body Exp_Aggr is
                     E_Discriminant
                   then
                      Remove (Comp);
+                     Num_Disc := Num_Disc + 1;
                   end if;
                end loop;
 
-               --  Insert girder discriminant associations
-               --  in the correct order
+               --  Insert stored discriminant associations in the correct
+               --  order. If there are more stored discriminants than new
+               --  discriminants, there is at least one new discriminant
+               --  that constrains more than one of the stored discriminants.
+               --  In this case we need to construct a proper subtype of
+               --  the parent type, in order to supply values to all the
+               --  components. Otherwise there is one-one correspondence
+               --  between the constraints and the stored discriminants.
 
                First_Comp := Empty;
-               Discriminant := First_Girder_Discriminant (Typ);
-               while Present (Discriminant) loop
-                  New_Comp :=
-                    Make_Component_Association (Loc,
-                      Choices    =>
-                        New_List (New_Occurrence_Of (Discriminant, Loc)),
 
-                      Expression =>
-                        New_Copy_Tree (
-                          Get_Discriminant_Value (
-                              Discriminant,
-                              Typ,
-                              Discriminant_Constraint (Typ))));
-
-                  if No (First_Comp) then
-                     Prepend_To (Component_Associations (N), New_Comp);
-                  else
-                     Insert_After (First_Comp, New_Comp);
-                  end if;
+               Discriminant := First_Stored_Discriminant (Base_Type (Typ));
 
-                  First_Comp := New_Comp;
-                  Next_Girder_Discriminant (Discriminant);
+               while Present (Discriminant) loop
+                  Num_Gird := Num_Gird + 1;
+                  Next_Stored_Discriminant (Discriminant);
                end loop;
-            end;
+
+               --  Case of more stored discriminants than new discriminants
+
+               if Num_Gird > Num_Disc then
+
+                  --  Create a proper subtype of the parent type, which is
+                  --  the proper implementation type for the aggregate, and
+                  --  convert it to the intended target type.
+
+                  Discriminant := First_Stored_Discriminant (Base_Type (Typ));
+
+                  while Present (Discriminant) loop
+                     New_Comp :=
+                       New_Copy_Tree (
+                         Get_Discriminant_Value (
+                             Discriminant,
+                             Typ,
+                             Discriminant_Constraint (Typ)));
+                     Append (New_Comp, Constraints);
+                     Next_Stored_Discriminant (Discriminant);
+                  end loop;
+
+                  Decl :=
+                    Make_Subtype_Declaration (Loc,
+                      Defining_Identifier =>
+                         Make_Defining_Identifier (Loc,
+                            New_Internal_Name ('T')),
+                      Subtype_Indication =>
+                        Make_Subtype_Indication (Loc,
+                          Subtype_Mark =>
+                            New_Occurrence_Of (Etype (Base_Type (Typ)), Loc),
+                          Constraint =>
+                            Make_Index_Or_Discriminant_Constraint
+                              (Loc, Constraints)));
+
+                  Insert_Action (N, Decl);
+                  Prepend_Stored_Values (Base_Type (Typ));
+
+                  Set_Etype (N, Defining_Identifier (Decl));
+                  Set_Analyzed (N);
+
+                  Rewrite (N, Unchecked_Convert_To (Typ, N));
+                  Analyze (N);
+
+               --  Case where we do not have fewer new discriminants than
+               --  stored discriminants, so in this case we can simply
+               --  use the stored discriminants of the subtype.
+
+               else
+                  Prepend_Stored_Values (Typ);
+               end if;
+            end Generate_Aggregate_For_Derived_Type;
          end if;
 
          if Is_Tagged_Type (Typ) then
@@ -3839,13 +4669,61 @@ package body Exp_Aggr is
       end if;
    end Expand_Record_Aggregate;
 
+   ----------------------------
+   -- Has_Default_Init_Comps --
+   ----------------------------
+
+   function Has_Default_Init_Comps (N : Node_Id) return Boolean is
+      Comps : constant List_Id := Component_Associations (N);
+      C     : Node_Id;
+      Expr  : Node_Id;
+   begin
+      pragma Assert (Nkind (N) = N_Aggregate
+         or else Nkind (N) = N_Extension_Aggregate);
+
+      if No (Comps) then
+         return False;
+      end if;
+
+      --  Check if any direct component has default initialized components
+
+      C := First (Comps);
+      while Present (C) loop
+         if Box_Present (C) then
+            return True;
+         end if;
+
+         Next (C);
+      end loop;
+
+      --  Recursive call in case of aggregate expression
+
+      C := First (Comps);
+      while Present (C) loop
+         Expr := Expression (C);
+
+         if Present (Expr)
+           and then (Nkind (Expr) = N_Aggregate
+                     or else Nkind (Expr) = N_Extension_Aggregate)
+           and then Has_Default_Init_Comps (Expr)
+         then
+            return True;
+         end if;
+
+         Next (C);
+      end loop;
+
+      return False;
+   end Has_Default_Init_Comps;
+
    --------------------------
    -- Is_Delayed_Aggregate --
    --------------------------
 
    function Is_Delayed_Aggregate (N : Node_Id) return Boolean is
-      Node : Node_Id := N;
+      Node : Node_Id   := N;
       Kind : Node_Kind := Nkind (Node);
+
    begin
       if Kind = N_Qualified_Expression then
          Node := Expression (Node);
@@ -3867,23 +4745,23 @@ package body Exp_Aggr is
      (N      : Node_Id;
       Typ    : Entity_Id;
       Target : Node_Id;
-      Flist  : Node_Id := Empty;
-      Obj    : Entity_Id := Empty)
-
-      return   List_Id is
-
+      Flist  : Node_Id   := Empty;
+      Obj    : Entity_Id := Empty) return List_Id
+   is
    begin
       if Is_Record_Type (Etype (N)) then
          return Build_Record_Aggr_Code (N, Typ, Target, Flist, Obj);
-      else
+
+      else pragma Assert (Is_Array_Type (Etype (N)));
          return
            Build_Array_Aggr_Code
-             (N,
-              First_Index (Typ),
-              Target,
-              Is_Scalar_Type (Component_Type (Typ)),
-              No_List,
-              Flist);
+             (N           => N,
+              Ctype       => Component_Type (Etype (N)),
+              Index       => First_Index (Typ),
+              Into        => Target,
+              Scalar_Comp => Is_Scalar_Type (Component_Type (Typ)),
+              Indices     => No_List,
+              Flist       => Flist);
       end if;
    end Late_Expansion;
 
@@ -3894,8 +4772,7 @@ package body Exp_Aggr is
    function Make_OK_Assignment_Statement
      (Sloc       : Source_Ptr;
       Name       : Node_Id;
-      Expression : Node_Id)
-      return       Node_Id
+      Expression : Node_Id) return Node_Id
    is
    begin
       Set_Assignment_OK (Name);
@@ -3936,26 +4813,297 @@ package body Exp_Aggr is
       return Nb_Choices;
    end Number_Of_Choices;
 
+   ------------------------------------
+   -- Packed_Array_Aggregate_Handled --
+   ------------------------------------
+
+   --  The current version of this procedure will handle at compile time
+   --  any array aggregate that meets these conditions:
+
+   --    One dimensional, bit packed
+   --    Underlying packed type is modular type
+   --    Bounds are within 32-bit Int range
+   --    All bounds and values are static
+
+   function Packed_Array_Aggregate_Handled (N : Node_Id) return Boolean is
+      Loc  : constant Source_Ptr := Sloc (N);
+      Typ  : constant Entity_Id  := Etype (N);
+      Ctyp : constant Entity_Id  := Component_Type (Typ);
+
+      Not_Handled : exception;
+      --  Exception raised if this aggregate cannot be handled
+
+   begin
+      --  For now, handle only one dimensional bit packed arrays
+
+      if not Is_Bit_Packed_Array (Typ)
+        or else Number_Dimensions (Typ) > 1
+        or else not Is_Modular_Integer_Type (Packed_Array_Type (Typ))
+      then
+         return False;
+      end if;
+
+      declare
+         Csiz  : constant Nat := UI_To_Int (Component_Size (Typ));
+
+         Lo : Node_Id;
+         Hi : Node_Id;
+         --  Bounds of index type
+
+         Lob : Uint;
+         Hib : Uint;
+         --  Values of bounds if compile time known
+
+         function Get_Component_Val (N : Node_Id) return Uint;
+         --  Given a expression value N of the component type Ctyp, returns
+         --  A value of Csiz (component size) bits representing this value.
+         --  If the value is non-static or any other reason exists why the
+         --  value cannot be returned, then Not_Handled is raised.
+
+         -----------------------
+         -- Get_Component_Val --
+         -----------------------
+
+         function Get_Component_Val (N : Node_Id) return Uint is
+            Val  : Uint;
+
+         begin
+            --  We have to analyze the expression here before doing any further
+            --  processing here. The analysis of such expressions is deferred
+            --  till expansion to prevent some problems of premature analysis.
+
+            Analyze_And_Resolve (N, Ctyp);
+
+            --  Must have a compile time value. String literals have to
+            --  be converted into temporaries as well, because they cannot
+            --  easily be converted into their bit representation.
+
+            if not Compile_Time_Known_Value (N)
+              or else Nkind (N) = N_String_Literal
+            then
+               raise Not_Handled;
+            end if;
+
+            Val := Expr_Rep_Value (N);
+
+            --  Adjust for bias, and strip proper number of bits
+
+            if Has_Biased_Representation (Ctyp) then
+               Val := Val - Expr_Value (Type_Low_Bound (Ctyp));
+            end if;
+
+            return Val mod Uint_2 ** Csiz;
+         end Get_Component_Val;
+
+      --  Here we know we have a one dimensional bit packed array
+
+      begin
+         Get_Index_Bounds (First_Index (Typ), Lo, Hi);
+
+         --  Cannot do anything if bounds are dynamic
+
+         if not Compile_Time_Known_Value (Lo)
+              or else
+            not Compile_Time_Known_Value (Hi)
+         then
+            return False;
+         end if;
+
+         --  Or are silly out of range of int bounds
+
+         Lob := Expr_Value (Lo);
+         Hib := Expr_Value (Hi);
+
+         if not UI_Is_In_Int_Range (Lob)
+              or else
+            not UI_Is_In_Int_Range (Hib)
+         then
+            return False;
+         end if;
+
+         --  At this stage we have a suitable aggregate for handling
+         --  at compile time (the only remaining checks, are that the
+         --  values of expressions in the aggregate are compile time
+         --  known (check performed by Get_Component_Val), and that
+         --  any subtypes or ranges are statically known.
+
+         --  If the aggregate is not fully positional at this stage,
+         --  then convert it to positional form. Either this will fail,
+         --  in which case we can do nothing, or it will succeed, in
+         --  which case we have succeeded in handling the aggregate,
+         --  or it will stay an aggregate, in which case we have failed
+         --  to handle this case.
+
+         if Present (Component_Associations (N)) then
+            Convert_To_Positional
+             (N, Max_Others_Replicate => 64, Handle_Bit_Packed => True);
+            return Nkind (N) /= N_Aggregate;
+         end if;
+
+         --  Otherwise we are all positional, so convert to proper value
+
+         declare
+            Lov : constant Nat := UI_To_Int (Lob);
+            Hiv : constant Nat := UI_To_Int (Hib);
+
+            Len : constant Nat := Int'Max (0, Hiv - Lov + 1);
+            --  The length of the array (number of elements)
+
+            Aggregate_Val : Uint;
+            --  Value of aggregate. The value is set in the low order
+            --  bits of this value. For the little-endian case, the
+            --  values are stored from low-order to high-order and
+            --  for the big-endian case the values are stored from
+            --  high-order to low-order. Note that gigi will take care
+            --  of the conversions to left justify the value in the big
+            --  endian case (because of left justified modular type
+            --  processing), so we do not have to worry about that here.
+
+            Lit : Node_Id;
+            --  Integer literal for resulting constructed value
+
+            Shift : Nat;
+            --  Shift count from low order for next value
+
+            Incr : Int;
+            --  Shift increment for loop
+
+            Expr : Node_Id;
+            --  Next expression from positional parameters of aggregate
+
+         begin
+            --  For little endian, we fill up the low order bits of the
+            --  target value. For big endian we fill up the high order
+            --  bits of the target value (which is a left justified
+            --  modular value).
+
+            if Bytes_Big_Endian xor Debug_Flag_8 then
+               Shift := Csiz * (Len - 1);
+               Incr  := -Csiz;
+            else
+               Shift := 0;
+               Incr  := +Csiz;
+            end if;
+
+            --  Loop to set the values
+
+            if Len = 0 then
+               Aggregate_Val := Uint_0;
+            else
+               Expr := First (Expressions (N));
+               Aggregate_Val := Get_Component_Val (Expr) * Uint_2 ** Shift;
+
+               for J in 2 .. Len loop
+                  Shift := Shift + Incr;
+                  Next (Expr);
+                  Aggregate_Val :=
+                    Aggregate_Val + Get_Component_Val (Expr) * Uint_2 ** Shift;
+               end loop;
+            end if;
+
+            --  Now we can rewrite with the proper value
+
+            Lit :=
+              Make_Integer_Literal (Loc,
+                Intval => Aggregate_Val);
+            Set_Print_In_Hex (Lit);
+
+            --  Construct the expression using this literal. Note that it is
+            --  important to qualify the literal with its proper modular type
+            --  since universal integer does not have the required range and
+            --  also this is a left justified modular type, which is important
+            --  in the big-endian case.
+
+            Rewrite (N,
+              Unchecked_Convert_To (Typ,
+                Make_Qualified_Expression (Loc,
+                  Subtype_Mark =>
+                    New_Occurrence_Of (Packed_Array_Type (Typ), Loc),
+                  Expression   => Lit)));
+
+            Analyze_And_Resolve (N, Typ);
+            return True;
+         end;
+      end;
+
+   exception
+      when Not_Handled =>
+         return False;
+   end Packed_Array_Aggregate_Handled;
+
+   ----------------------------
+   -- Has_Mutable_Components --
+   ----------------------------
+
+   function Has_Mutable_Components (Typ : Entity_Id) return Boolean is
+      Comp : Entity_Id;
+
+   begin
+      Comp := First_Component (Typ);
+
+      while Present (Comp) loop
+         if Is_Record_Type (Etype (Comp))
+           and then Has_Discriminants (Etype (Comp))
+           and then not Is_Constrained (Etype (Comp))
+         then
+            return True;
+         end if;
+
+         Next_Component (Comp);
+      end loop;
+
+      return False;
+   end Has_Mutable_Components;
+
+   ------------------------------
+   -- Initialize_Discriminants --
+   ------------------------------
+
+   procedure Initialize_Discriminants (N : Node_Id; Typ : Entity_Id) is
+      Loc  : constant Source_Ptr := Sloc (N);
+      Bas  : constant Entity_Id  := Base_Type (Typ);
+      Par  : constant Entity_Id  := Etype (Bas);
+      Decl : constant Node_Id    := Parent (Par);
+      Ref  : Node_Id;
+
+   begin
+      if Is_Tagged_Type (Bas)
+        and then Is_Derived_Type (Bas)
+        and then Has_Discriminants (Par)
+        and then Has_Discriminants (Bas)
+        and then Number_Discriminants (Bas) /= Number_Discriminants (Par)
+        and then Nkind (Decl) = N_Full_Type_Declaration
+        and then Nkind (Type_Definition (Decl)) = N_Record_Definition
+        and then Present
+          (Variant_Part (Component_List (Type_Definition (Decl))))
+        and then Nkind (N) /= N_Extension_Aggregate
+      then
+
+         --   Call init proc to set discriminants.
+         --   There should eventually be a special procedure for this ???
+
+         Ref := New_Reference_To (Defining_Identifier (N), Loc);
+         Insert_Actions_After (N,
+           Build_Initialization_Call (Sloc (N), Ref, Typ));
+      end if;
+   end Initialize_Discriminants;
+
    ---------------------------
    -- Safe_Slice_Assignment --
    ---------------------------
 
-   function Safe_Slice_Assignment
-     (N    : Node_Id;
-      Typ  : Entity_Id)
-      return Boolean
-   is
+   function Safe_Slice_Assignment (N : Node_Id) return Boolean is
       Loc        : constant Source_Ptr := Sloc (Parent (N));
       Pref       : constant Node_Id    := Prefix (Name (Parent (N)));
       Range_Node : constant Node_Id    := Discrete_Range (Name (Parent (N)));
       Expr       : Node_Id;
-      L_I        : Entity_Id;
+      L_J        : Entity_Id;
       L_Iter     : Node_Id;
       L_Body     : Node_Id;
       Stat       : Node_Id;
 
    begin
-      --  Generate: For J in Range loop Pref (I) := Expr; end loop;
+      --  Generate: for J in Range loop Pref (J) := Expr; end loop;
 
       if Comes_From_Source (N)
         and then No (Expressions (N))
@@ -3964,14 +5112,14 @@ package body Exp_Aggr is
       then
          Expr :=
            Expression (First (Component_Associations (N)));
-         L_I := Make_Defining_Identifier (Loc, New_Internal_Name ('I'));
+         L_J := Make_Defining_Identifier (Loc, New_Internal_Name ('J'));
 
          L_Iter :=
            Make_Iteration_Scheme (Loc,
              Loop_Parameter_Specification =>
                Make_Loop_Parameter_Specification
                  (Loc,
-                  Defining_Identifier         => L_I,
+                  Defining_Identifier         => L_J,
                   Discrete_Subtype_Definition => Relocate_Node (Range_Node)));
 
          L_Body :=
@@ -3979,7 +5127,7 @@ package body Exp_Aggr is
               Name =>
                 Make_Indexed_Component (Loc,
                   Prefix      => Relocate_Node (Pref),
-                  Expressions => New_List (New_Occurrence_Of (L_I, Loc))),
+                  Expressions => New_List (New_Occurrence_Of (L_J, Loc))),
                Expression => Relocate_Node (Expr));
 
          --  Construct the final loop
@@ -3991,6 +5139,11 @@ package body Exp_Aggr is
               Iteration_Scheme => L_Iter,
               Statements       => New_List (L_Body));
 
+         --  Set type of aggregate to be type of lhs in assignment,
+         --  to suppress redundant length checks.
+
+         Set_Etype (N, Etype (Name (Parent (N))));
+
          Rewrite (Parent (N), Stat);
          Analyze (Parent (N));
          return True;
@@ -4005,8 +5158,8 @@ package body Exp_Aggr is
    ---------------------
 
    procedure Sort_Case_Table (Case_Table : in out Case_Table_Type) is
-      L : Int := Case_Table'First;
-      U : Int := Case_Table'Last;
+      L : constant Int := Case_Table'First;
+      U : constant Int := Case_Table'Last;
       K : Int;
       J : Int;
       T : Case_Bounds;