OSDN Git Service

2007-04-20 Ed Schonberg <schonberg@adacore.com>
[pf3gnuchains/gcc-fork.git] / gcc / ada / sem_aggr.adb
index aa7cddf..87204e7 100644 (file)
@@ -6,7 +6,7 @@
 --                                                                          --
 --                                 B o d y                                  --
 --                                                                          --
---          Copyright (C) 1992-2005 Free Software Foundation, Inc.          --
+--          Copyright (C) 1992-2007, 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- --
@@ -16,8 +16,8 @@
 -- or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License --
 -- for  more details.  You should have  received  a copy of the GNU General --
 -- Public License  distributed with GNAT;  see file COPYING.  If not, write --
--- to  the Free Software Foundation,  59 Temple Place - Suite 330,  Boston, --
--- MA 02111-1307, USA.                                                      --
+-- to  the  Free Software Foundation,  51  Franklin  Street,  Fifth  Floor, --
+-- Boston, MA 02110-1301, USA.                                              --
 --                                                                          --
 -- GNAT was originally developed  by the GNAT team at  New York University. --
 -- Extensive contributions were provided by Ada Core Technologies Inc.      --
@@ -29,16 +29,20 @@ with Checks;   use Checks;
 with Einfo;    use Einfo;
 with Elists;   use Elists;
 with Errout;   use Errout;
+with Exp_Tss;  use Exp_Tss;
 with Exp_Util; use Exp_Util;
 with Freeze;   use Freeze;
 with Itypes;   use Itypes;
+with Lib;      use Lib;
 with Lib.Xref; use Lib.Xref;
 with Namet;    use Namet;
 with Nmake;    use Nmake;
 with Nlists;   use Nlists;
 with Opt;      use Opt;
+with Rtsfind;  use Rtsfind;
 with Sem;      use Sem;
 with Sem_Cat;  use Sem_Cat;
+with Sem_Ch3;  use Sem_Ch3;
 with Sem_Ch8;  use Sem_Ch8;
 with Sem_Ch13; use Sem_Ch13;
 with Sem_Eval; use Sem_Eval;
@@ -77,8 +81,17 @@ package body Sem_Aggr is
    --  statement of variant part will usually be small and probably in near
    --  sorted order.
 
-   procedure Check_Can_Never_Be_Null (N : Node_Id; Expr : Node_Id);
-   --  Ada 2005 (AI-231): Check bad usage of the null-exclusion issue
+   procedure Check_Can_Never_Be_Null (Typ : Entity_Id; Expr : Node_Id);
+   --  Ada 2005 (AI-231): Check bad usage of null for a component for which
+   --  null exclusion (NOT NULL) is specified. Typ can be an E_Array_Type for
+   --  the array case (the component type of the array will be used) or an
+   --  E_Component/E_Discriminant entity in the record case, in which case the
+   --  type of the component will be used for the test. If Typ is any other
+   --  kind of entity, the call is ignored. Expr is the component node in the
+   --  aggregate which is an explicit occurrence of NULL. An error will be
+   --  issued if the component is null excluding.
+   --
+   --  It would be better to pass the proper type for Typ ???
 
    ------------------------------------------------------
    -- Subprograms used for RECORD AGGREGATE Processing --
@@ -93,28 +106,28 @@ package body Sem_Aggr is
    --    N is the N_Aggregate node.
    --    Typ is the record type for the aggregate resolution
    --
-   --  While performing the semantic checks, this procedure
-   --  builds a new Component_Association_List where each record field
-   --  appears alone in a Component_Choice_List along with its corresponding
-   --  expression. The record fields in the Component_Association_List
-   --  appear in the same order in which they appear in the record type Typ.
+   --  While performing the semantic checks, this procedure builds a new
+   --  Component_Association_List where each record field appears alone in a
+   --  Component_Choice_List along with its corresponding expression. The
+   --  record fields in the Component_Association_List appear in the same order
+   --  in which they appear in the record type Typ.
    --
-   --  Once this new Component_Association_List is built and all the
-   --  semantic checks performed, the original aggregate subtree is replaced
-   --  with the new named record aggregate just built. Note that the subtree
-   --  substitution is performed with Rewrite so as to be
-   --  able to retrieve the original aggregate.
+   --  Once this new Component_Association_List is built and all the semantic
+   --  checks performed, the original aggregate subtree is replaced with the
+   --  new named record aggregate just built. Note that subtree substitution is
+   --  performed with Rewrite so as to be able to retrieve the original
+   --  aggregate.
    --
    --  The aggregate subtree manipulation performed by Resolve_Record_Aggregate
    --  yields the aggregate format expected by Gigi. Typically, this kind of
    --  tree manipulations are done in the expander. However, because the
-   --  semantic checks that need to be performed on record aggregates really
-   --  go hand in hand with the record aggregate normalization, the aggregate
+   --  semantic checks that need to be performed on record aggregates really go
+   --  hand in hand with the record aggregate normalization, the aggregate
    --  subtree transformation is performed during resolution rather than
-   --  expansion. Had we decided otherwise we would have had to duplicate
-   --  most of the code in the expansion procedure Expand_Record_Aggregate.
-   --  Note, however, that all the expansion concerning aggegates for tagged
-   --  records is done in Expand_Record_Aggregate.
+   --  expansion. Had we decided otherwise we would have had to duplicate most
+   --  of the code in the expansion procedure Expand_Record_Aggregate. Note,
+   --  however, that all the expansion concerning aggregates for tagged records
+   --  is done in Expand_Record_Aggregate.
    --
    --  The algorithm of Resolve_Record_Aggregate proceeds as follows:
    --
@@ -166,7 +179,7 @@ package body Sem_Aggr is
    --     should we not find such values or should they be duplicated.
    --
    --  7. We then make sure no illegal component names appear in the
-   --     record aggegate and make sure that the type of the record
+   --     record aggregate and make sure that the type of the record
    --     components appearing in a same choice list is the same.
    --     Finally we ensure that the others choice, if present, is
    --     used to provide the value of at least a record component.
@@ -341,7 +354,7 @@ package body Sem_Aggr is
    --  those defined by the aggregate. When this routine is invoked
    --  Resolve_Array_Aggregate has already processed aggregate N. Thus the
    --  Aggregate_Bounds of each sub-aggregate, is an N_Range node giving the
-   --  sub-aggregate bounds. When building the aggegate itype, this function
+   --  sub-aggregate bounds. When building the aggregate itype, this function
    --  traverses the array aggregate N collecting such Aggregate_Bounds and
    --  constructs the proper array aggregate itype.
    --
@@ -440,8 +453,12 @@ package body Sem_Aggr is
             Apply_Scalar_Range_Check (Exp, Check_Typ);
          end if;
 
+      --  Verify that target type is also scalar, to prevent view anomalies
+      --  in instantiations.
+
       elsif (Is_Scalar_Type (Exp_Typ)
-             or else Nkind (Exp) = N_String_Literal)
+              or else Nkind (Exp) = N_String_Literal)
+        and then Is_Scalar_Type (Check_Typ)
         and then Exp_Typ /= Check_Typ
       then
          if Is_Entity_Name (Exp)
@@ -468,12 +485,16 @@ package body Sem_Aggr is
             Check_Unset_Reference (Exp);
          end if;
 
+      --  Ada 2005 (AI-230): Generate a conversion to an anonymous access
+      --  component's type to force the appropriate accessibility checks.
+
       --  Ada 2005 (AI-231): Generate conversion to the null-excluding
       --  type to force the corresponding run-time check
 
       elsif Is_Access_Type (Check_Typ)
-        and then Can_Never_Be_Null (Check_Typ)
-        and then not Can_Never_Be_Null (Exp_Typ)
+        and then ((Is_Local_Anonymous_Access (Check_Typ))
+                    or else (Can_Never_Be_Null (Check_Typ)
+                               and then not Can_Never_Be_Null (Exp_Typ)))
       then
          Rewrite (Exp, Convert_To (Check_Typ, Relocate_Node (Exp)));
          Analyze_And_Resolve (Exp, Check_Typ);
@@ -491,14 +512,14 @@ package body Sem_Aggr is
       return Entity_Id
    is
       Aggr_Dimension : constant Pos := Number_Dimensions (Typ);
-      --  Number of aggregate index dimensions.
+      --  Number of aggregate index dimensions
 
       Aggr_Range : array (1 .. Aggr_Dimension) of Node_Id := (others => Empty);
-      --  Constrained N_Range of each index dimension in our aggregate itype.
+      --  Constrained N_Range of each index dimension in our aggregate itype
 
       Aggr_Low   : array (1 .. Aggr_Dimension) of Node_Id := (others => Empty);
       Aggr_High  : array (1 .. Aggr_Dimension) of Node_Id := (others => Empty);
-      --  Low and High bounds for each index dimension in our aggregate itype.
+      --  Low and High bounds for each index dimension in our aggregate itype
 
       Is_Fully_Positional : Boolean := True;
 
@@ -507,6 +528,7 @@ package body Sem_Aggr is
       --  (sub-)aggregate N. This procedure collects the constrained N_Range
       --  nodes corresponding to each index dimension of our aggregate itype.
       --  These N_Range nodes are collected in Aggr_Range above.
+      --
       --  Likewise collect in Aggr_Low & Aggr_High above the low and high
       --  bounds of each index dimension. If, when collecting, two bounds
       --  corresponding to the same dimension are static and found to differ,
@@ -518,11 +540,11 @@ package body Sem_Aggr is
 
       procedure Collect_Aggr_Bounds (N : Node_Id; Dim : Pos) is
          This_Range : constant Node_Id := Aggregate_Bounds (N);
-         --  The aggregate range node of this specific sub-aggregate.
+         --  The aggregate range node of this specific sub-aggregate
 
          This_Low  : constant Node_Id := Low_Bound (Aggregate_Bounds (N));
          This_High : constant Node_Id := High_Bound (Aggregate_Bounds (N));
-         --  The aggregate bounds of this specific sub-aggregate.
+         --  The aggregate bounds of this specific sub-aggregate
 
          Assoc : Node_Id;
          Expr  : Node_Id;
@@ -543,9 +565,9 @@ package body Sem_Aggr is
 
                elsif Expr_Value (This_Low) /= Expr_Value (Aggr_Low (Dim)) then
                   Set_Raises_Constraint_Error (N);
-                  Error_Msg_N ("Sub-aggregate low bound mismatch?", N);
-                  Error_Msg_N ("Constraint_Error will be raised at run-time?",
-                               N);
+                  Error_Msg_N ("sub-aggregate low bound mismatch?", N);
+                  Error_Msg_N
+                     ("\Constraint_Error will be raised at run-time?", N);
                end if;
             end if;
 
@@ -557,9 +579,9 @@ package body Sem_Aggr is
                  Expr_Value (This_High) /= Expr_Value (Aggr_High (Dim))
                then
                   Set_Raises_Constraint_Error (N);
-                  Error_Msg_N ("Sub-aggregate high bound mismatch?", N);
-                  Error_Msg_N ("Constraint_Error will be raised at run-time?",
-                               N);
+                  Error_Msg_N ("sub-aggregate high bound mismatch?", N);
+                  Error_Msg_N
+                     ("\Constraint_Error will be raised at run-time?", N);
                end if;
             end if;
          end if;
@@ -597,7 +619,7 @@ package body Sem_Aggr is
       --  the final itype of the overall aggregate
 
       Index_Constraints : constant List_Id := New_List;
-      --  The list of index constraints of the aggregate itype.
+      --  The list of index constraints of the aggregate itype
 
    --  Start of processing for Array_Aggr_Subtype
 
@@ -608,7 +630,7 @@ package body Sem_Aggr is
       Set_Parent (Index_Constraints, N);
       Collect_Aggr_Bounds (N, 1);
 
-      --  Build the list of constrained indices of our aggregate itype.
+      --  Build the list of constrained indices of our aggregate itype
 
       for J in 1 .. Aggr_Dimension loop
          Create_Index : declare
@@ -662,15 +684,32 @@ package body Sem_Aggr is
       Set_Is_Internal    (Itype, True);
       Init_Size_Align    (Itype);
 
+      --  Handle aggregate initializing statically allocated dispatch table
+
+      if Static_Dispatch_Tables
+        and then VM_Target = No_VM
+        and then RTU_Loaded (Ada_Tags)
+
+         --  Avoid circularity when rebuilding the compiler
+
+        and then Cunit_Entity (Get_Source_Unit (N)) /= RTU_Entity (Ada_Tags)
+        and then (Etype (N) = RTE (RE_Address_Array)
+                    or else
+                  Base_Type (Etype (N)) = RTE (RE_Tag_Table))
+      then
+         Set_Size_Known_At_Compile_Time (Itype);
+
       --  A simple optimization: purely positional aggregates of static
       --  components should be passed to gigi unexpanded whenever possible,
       --  and regardless of the staticness of the bounds themselves. Subse-
       --  quent checks in exp_aggr verify that type is not packed, etc.
 
-      Set_Size_Known_At_Compile_Time (Itype,
-         Is_Fully_Positional
-           and then Comes_From_Source (N)
-           and then Size_Known_At_Compile_Time (Component_Type (Typ)));
+      else
+         Set_Size_Known_At_Compile_Time (Itype,
+            Is_Fully_Positional
+              and then Comes_From_Source (N)
+              and then Size_Known_At_Compile_Time (Component_Type (Typ)));
+      end if;
 
       --  We always need a freeze node for a packed array subtype, so that
       --  we can build the Packed_Array_Type corresponding to the subtype.
@@ -716,13 +755,10 @@ package body Sem_Aggr is
                 Name_Buffer (1 .. Name_Len);
 
       begin
-
          Component_Elmt := First_Elmt (Elements);
-
          while Nr_Of_Suggestions <= Max_Suggestions
             and then Present (Component_Elmt)
          loop
-
             Get_Name_String (Chars (Node (Component_Elmt)));
 
             if Is_Bad_Spelling_Of (Name_Buffer (1 .. Name_Len), S) then
@@ -773,9 +809,7 @@ package body Sem_Aggr is
       end if;
 
       Comp := First_Component (T);
-
       while Present (Comp) loop
-
          if Is_Scalar_Type (Etype (Comp)) then
             null;
 
@@ -786,15 +820,12 @@ package body Sem_Aggr is
             null;
 
          elsif Is_Array_Type (Etype (Comp)) then
-
             if Is_Bit_Packed_Array (Etype (Comp)) then
                return;
             end if;
 
             Ind := First_Index (Etype (Comp));
-
             while Present (Ind) loop
-
                if Nkind (Ind) /= N_Range
                  or else Nkind (Low_Bound (Ind)) /= N_Integer_Literal
                  or else Nkind (High_Bound (Ind)) /= N_Integer_Literal
@@ -812,7 +843,7 @@ package body Sem_Aggr is
          Next_Component (Comp);
       end loop;
 
-      --  On exit, all components have statically known sizes.
+      --  On exit, all components have statically known sizes
 
       Set_Size_Known_At_Compile_Time (T);
    end Check_Static_Discriminated_Subtype;
@@ -879,15 +910,9 @@ package body Sem_Aggr is
          Error_Msg_CRT ("aggregate", N);
       end if;
 
-      if Is_Limited_Composite (Typ) then
-         Error_Msg_N ("aggregate type cannot have limited component", N);
-         Explain_Limited_Type (Typ, N);
-
       --  Ada 2005 (AI-287): Limited aggregates allowed
 
-      elsif Is_Limited_Type (Typ)
-        and Ada_Version < Ada_05
-      then
+      if Is_Limited_Type (Typ) and then Ada_Version < Ada_05 then
          Error_Msg_N ("aggregate type cannot be limited", N);
          Explain_Limited_Type (Typ, N);
 
@@ -974,7 +999,14 @@ package body Sem_Aggr is
             --  in which the array aggregate occurs. If the context does not
             --  permit it, or the aggregate type is unconstrained, an others
             --  choice is not allowed.
-            --
+
+            --  If expansion is disabled (generic context, or semantics-only
+            --  mode) actual subtypes cannot be constructed, and the type of
+            --  an object may be its unconstrained nominal type. However, if
+            --  the context is an assignment, we assume that "others" is
+            --  allowed, because the target of the assignment will have a
+            --  constrained subtype when fully compiled.
+
             --  Note that there is no node for Explicit_Actual_Parameter.
             --  To test for this context we therefore have to test for node
             --  N_Parameter_Association which itself appears only if there is a
@@ -983,13 +1015,6 @@ package body Sem_Aggr is
 
             Set_Etype (N, Aggr_Typ);  --  may be overridden later on
 
-            --  Ada 2005 (AI-231): Propagate the null_exclusion attribute to
-            --  the components of the array aggregate
-
-            if Ada_Version >= Ada_05 then
-               Set_Can_Never_Be_Null (Aggr_Typ, Can_Never_Be_Null (Typ));
-            end if;
-
             if Is_Constrained (Typ) and then
               (Pkind = N_Assignment_Statement      or else
                Pkind = N_Parameter_Association     or else
@@ -1014,6 +1039,16 @@ package body Sem_Aggr is
                     Component_Typ  => Component_Type (Typ),
                     Others_Allowed => True);
 
+            elsif not Expander_Active
+              and then Pkind = N_Assignment_Statement
+            then
+               Aggr_Resolved :=
+                 Resolve_Array_Aggregate
+                   (N,
+                    Index          => First_Index (Aggr_Typ),
+                    Index_Constr   => First_Index (Typ),
+                    Component_Typ  => Component_Type (Typ),
+                    Others_Allowed => True);
             else
                Aggr_Resolved :=
                  Resolve_Array_Aggregate
@@ -1033,9 +1068,15 @@ package body Sem_Aggr is
             Set_Etype (N, Aggr_Subtyp);
          end Array_Aggregate;
 
+      elsif Is_Private_Type (Typ)
+        and then Present (Full_View (Typ))
+        and then In_Inlined_Body
+        and then Is_Composite_Type (Full_View (Typ))
+      then
+         Resolve (N, Full_View (Typ));
+
       else
          Error_Msg_N ("illegal context for aggregate", N);
-
       end if;
 
       --  If we can determine statically that the evaluation of the
@@ -1102,7 +1143,7 @@ package body Sem_Aggr is
       --  warning if not and sets the Raises_Constraint_Error Flag in N.
 
       function Dynamic_Or_Null_Range (L, H : Node_Id) return Boolean;
-      --  Returns True if range L .. H is dynamic or null.
+      --  Returns True if range L .. H is dynamic or null
 
       procedure Get (Value : out Uint; From : Node_Id; OK : out Boolean);
       --  Given expression node From, this routine sets OK to False if it
@@ -1216,7 +1257,7 @@ package body Sem_Aggr is
          if OK_BH and then OK_AH and then Val_BH < Val_AH then
             Set_Raises_Constraint_Error (N);
             Error_Msg_N ("upper bound out of range?", AH);
-            Error_Msg_N ("Constraint_Error will be raised at run-time?", AH);
+            Error_Msg_N ("\Constraint_Error will be raised at run-time?", AH);
 
             --  You need to set AH to BH or else in the case of enumerations
             --  indices we will not be able to resolve the aggregate bounds.
@@ -1301,8 +1342,8 @@ package body Sem_Aggr is
 
          if Range_Len < Len then
             Set_Raises_Constraint_Error (N);
-            Error_Msg_N ("Too many elements?", N);
-            Error_Msg_N ("Constraint_Error will be raised at run-time?", N);
+            Error_Msg_N ("too many elements?", N);
+            Error_Msg_N ("\Constraint_Error will be raised at run-time?", N);
          end if;
       end Check_Length;
 
@@ -1364,10 +1405,10 @@ package body Sem_Aggr is
       is
          Nxt_Ind        : constant Node_Id := Next_Index (Index);
          Nxt_Ind_Constr : constant Node_Id := Next_Index (Index_Constr);
-         --  Index is the current index corresponding to the expresion.
+         --  Index is the current index corresponding to the expresion
 
          Resolution_OK : Boolean := True;
-         --  Set to False if resolution of the expression failed.
+         --  Set to False if resolution of the expression failed
 
       begin
          --  If the array type against which we are resolving the aggregate
@@ -1392,7 +1433,7 @@ package body Sem_Aggr is
                   --  aggregate must not be enclosed in parentheses.
 
                   if Paren_Count (Expr) /= 0 then
-                     Error_Msg_N ("No parenthesis allowed here", Expr);
+                     Error_Msg_N ("no parenthesis allowed here", Expr);
                   end if;
 
                   Make_String_Into_Aggregate (Expr);
@@ -1445,14 +1486,14 @@ package body Sem_Aggr is
 
       Aggr_Low  : Node_Id := Empty;
       Aggr_High : Node_Id := Empty;
-      --  The actual low and high bounds of this sub-aggegate
+      --  The actual low and high bounds of this sub-aggregate
 
       Choices_Low  : Node_Id := Empty;
       Choices_High : Node_Id := Empty;
       --  The lowest and highest discrete choices values for a named aggregate
 
       Nb_Elements : Uint := Uint_0;
-      --  The number of elements in a positional aggegate
+      --  The number of elements in a positional aggregate
 
       Others_Present : Boolean := False;
 
@@ -1580,11 +1621,10 @@ package body Sem_Aggr is
             --  in the current association.
 
          begin
-            --  STEP 2 (A): Check discrete choices validity.
+            --  STEP 2 (A): Check discrete choices validity
 
             Assoc := First (Component_Associations (N));
             while Present (Assoc) loop
-
                Prev_Nb_Discrete_Choices := Nb_Discrete_Choices;
                Choice := First (Choices (Assoc));
                loop
@@ -1633,7 +1673,7 @@ package body Sem_Aggr is
                   if Etype (Choice) = Any_Type then
                      return Failure;
 
-                  --  If the discrete choice raises CE get its original bounds.
+                  --  If the discrete choice raises CE get its original bounds
 
                   elsif Nkind (Choice) = N_Raise_Constraint_Error then
                      Set_Raises_Constraint_Error (N);
@@ -1664,6 +1704,7 @@ package body Sem_Aggr is
                   Next (Choice);
 
                   if No (Choice) then
+
                      --  Check if we have a single discrete choice and whether
                      --  this discrete choice specifies a single value.
 
@@ -1677,7 +1718,9 @@ package body Sem_Aggr is
 
                --  Ada 2005 (AI-231)
 
-               if Ada_Version >= Ada_05 then
+               if Ada_Version >= Ada_05
+                 and then Nkind (Expression (Assoc)) = N_Null
+               then
                   Check_Can_Never_Be_Null (Etype (N), Expression (Assoc));
                end if;
 
@@ -1807,7 +1850,9 @@ package body Sem_Aggr is
 
             --  Ada 2005 (AI-231)
 
-            if Ada_Version >= Ada_05 then
+            if Ada_Version >= Ada_05
+              and then Nkind (Expr) = N_Null
+            then
                Check_Can_Never_Be_Null (Etype (N), Expr);
             end if;
 
@@ -1823,9 +1868,10 @@ package body Sem_Aggr is
 
             --  Ada 2005 (AI-231)
 
-            if Ada_Version >= Ada_05 then
-               Check_Can_Never_Be_Null
-                 (Etype (N), Expression (Assoc));
+            if Ada_Version >= Ada_05
+              and then Nkind (Assoc) = N_Null
+            then
+               Check_Can_Never_Be_Null (Etype (N), Expression (Assoc));
             end if;
 
             --  Ada 2005 (AI-287): In case of default initialized component
@@ -1885,7 +1931,6 @@ package body Sem_Aggr is
          Check_Length (Aggr_Low, Aggr_High, Nb_Elements);
          Check_Length (Index_Typ_Low, Index_Typ_High, Nb_Elements);
          Check_Length (Index_Base_Low, Index_Base_High, Nb_Elements);
-
       end if;
 
       if Raises_Constraint_Error (Aggr_Low)
@@ -1899,8 +1944,7 @@ package body Sem_Aggr is
       --  Do not duplicate Aggr_High if Aggr_High = Aggr_Low + Nb_Elements
       --  since the addition node returned by Add is not yet analyzed. Attach
       --  to tree and analyze first. Reset analyzed flag to insure it will get
-      --  analyzed when it is a literal bound whose type must be properly
-      --  set.
+      --  analyzed when it is a literal bound whose type must be properly set.
 
       if Others_Present or else Nb_Discrete_Choices > 0 then
          Aggr_High := Duplicate_Subexpr (Aggr_High);
@@ -2023,10 +2067,9 @@ package body Sem_Aggr is
       elsif Nkind (A) /= N_Aggregate then
          if Is_Overloaded (A) then
             A_Type := Any_Type;
-            Get_First_Interp (A, I, It);
 
+            Get_First_Interp (A, I, It);
             while Present (It.Typ) loop
-
                if Is_Tagged_Type (It.Typ)
                   and then not Is_Limited_Type (It.Typ)
                then
@@ -2076,7 +2119,7 @@ package body Sem_Aggr is
          end if;
 
       else
-         Error_Msg_N (" No unique type for this aggregate",  A);
+         Error_Msg_N ("no unique type for this aggregate",  A);
       end if;
    end Resolve_Extension_Aggregate;
 
@@ -2085,6 +2128,18 @@ package body Sem_Aggr is
    ------------------------------
 
    procedure Resolve_Record_Aggregate (N : Node_Id; Typ : Entity_Id) is
+      Assoc : Node_Id;
+      --  N_Component_Association node belonging to the input aggregate N
+
+      Expr            : Node_Id;
+      Positional_Expr : Node_Id;
+      Component       : Entity_Id;
+      Component_Elmt  : Elmt_Id;
+
+      Components : constant Elist_Id := New_Elmt_List;
+      --  Components is the list of the record components whose value must
+      --  be provided in the aggregate. This list does include discriminants.
+
       New_Assoc_List : constant List_Id := New_List;
       New_Assoc      : Node_Id;
       --  New_Assoc_List is the newly built list of N_Component_Association
@@ -2104,19 +2159,19 @@ package body Sem_Aggr is
       --
       --  This variable is updated as a side effect of function Get_Value
 
-      Mbox_Present : Boolean := False;
-      Others_Mbox  : Boolean := False;
+      Is_Box_Present : Boolean := False;
+      Others_Box     : Boolean := False;
       --  Ada 2005 (AI-287): Variables used in case of default initialization
-      --  to provide a functionality similar to Others_Etype. Mbox_Present
+      --  to provide a functionality similar to Others_Etype. Box_Present
       --  indicates that the component takes its default initialization;
-      --  Others_Mbox indicates that at least one component takes its default
+      --  Others_Box indicates that at least one component takes its default
       --  initialization. Similar to Others_Etype, they are also updated as a
       --  side effect of function Get_Value.
 
       procedure Add_Association
-        (Component   : Entity_Id;
-         Expr        : Node_Id;
-         Box_Present : Boolean := False);
+        (Component      : Entity_Id;
+         Expr           : Node_Id;
+         Is_Box_Present : Boolean := False);
       --  Builds a new N_Component_Association node which associates
       --  Component to expression Expr and adds it to the new association
       --  list New_Assoc_List being built.
@@ -2164,9 +2219,9 @@ package body Sem_Aggr is
       ---------------------
 
       procedure Add_Association
-        (Component   : Entity_Id;
-         Expr        : Node_Id;
-         Box_Present : Boolean := False)
+        (Component      : Entity_Id;
+         Expr           : Node_Id;
+         Is_Box_Present : Boolean := False)
       is
          Choice_List : constant List_Id := New_List;
          New_Assoc   : Node_Id;
@@ -2177,7 +2232,7 @@ package body Sem_Aggr is
            Make_Component_Association (Sloc (Expr),
              Choices     => Choice_List,
              Expression  => Expr,
-             Box_Present => Box_Present);
+             Box_Present => Is_Box_Present);
          Append (New_Assoc, New_Assoc_List);
       end Add_Association;
 
@@ -2227,18 +2282,19 @@ package body Sem_Aggr is
             return True;
          end if;
 
-         --  Now look to see if Discr was specified in the ancestor part.
-
-         Orig_Discr := Original_Record_Component (Discr);
-         D          := First_Discriminant (Ancestor_Typ);
+         --  Now look to see if Discr was specified in the ancestor part
 
          if Ancestor_Is_Subtyp then
             D_Val := First_Elmt (Discriminant_Constraint (Entity (Ancestor)));
          end if;
 
+         Orig_Discr := Original_Record_Component (Discr);
+
+         D := First_Discriminant (Ancestor_Typ);
          while Present (D) loop
-            --  If Ancestor has already specified Disc value than
-            --  insert its value in the final aggregate.
+
+            --  If Ancestor has already specified Disc value than insert its
+            --  value in the final aggregate.
 
             if Original_Record_Component (D) = Orig_Discr then
                if Ancestor_Is_Subtyp then
@@ -2278,43 +2334,8 @@ package body Sem_Aggr is
          Expr          : Node_Id := Empty;
          Selector_Name : Node_Id;
 
-         procedure Check_Non_Limited_Type;
-         --  Relax check to allow the default initialization of limited types.
-         --  For example:
-         --      record
-         --         C : Lim := (..., others => <>);
-         --      end record;
-
-         ----------------------------
-         -- Check_Non_Limited_Type --
-         ----------------------------
-
-         procedure Check_Non_Limited_Type is
-         begin
-            if Is_Limited_Type (Etype (Compon))
-               and then Comes_From_Source (Compon)
-               and then not In_Instance_Body
-            then
-               --  Ada 2005 (AI-287): Limited aggregates are allowed
-
-               if Ada_Version >= Ada_05
-                 and then Present (Expression (Assoc))
-                 and then Nkind (Expression (Assoc)) = N_Aggregate
-               then
-                  null;
-               else
-                  Error_Msg_N
-                    ("initialization not allowed for limited types", N);
-                  Explain_Limited_Type (Etype (Compon), Compon);
-               end if;
-
-            end if;
-         end Check_Non_Limited_Type;
-
-      --  Start of processing for Get_Value
-
       begin
-         Mbox_Present := False;
+         Is_Box_Present := False;
 
          if Present (From) then
             Assoc := First (From);
@@ -2337,21 +2358,25 @@ package body Sem_Aggr is
 
                      --  Ada 2005 (AI-287): In case of default initialization
                      --  of components, we duplicate the corresponding default
-                     --  expression (from the record type declaration).
+                     --  expression (from the record type declaration). The
+                     --  copy must carry the sloc of the association (not the
+                     --  original expression) to prevent spurious elaboration
+                     --  checks when the default includes function calls.
 
                      if Box_Present (Assoc) then
-                        Others_Mbox  := True;
-                        Mbox_Present := True;
+                        Others_Box     := True;
+                        Is_Box_Present := True;
 
                         if Expander_Active then
-                           return New_Copy_Tree (Expression (Parent (Compon)));
+                           return
+                             New_Copy_Tree
+                               (Expression (Parent (Compon)),
+                                New_Sloc => Sloc (Assoc));
                         else
                            return Expression (Parent (Compon));
                         end if;
 
                      else
-                        Check_Non_Limited_Type;
-
                         if Present (Others_Etype) and then
                            Base_Type (Others_Etype) /= Base_Type (Etype
                                                                    (Compon))
@@ -2388,21 +2413,20 @@ package body Sem_Aggr is
                      --  Ada 2005 (AI-287)
 
                      if Box_Present (Assoc) then
-                        Mbox_Present := True;
+                        Is_Box_Present := True;
 
                         --  Duplicate the default expression of the component
-                        --  from the record type declaration
+                        --  from the record type declaration, so a new copy
+                        --  can be attached to the association.
 
-                        if Present (Next (Selector_Name)) then
-                           Expr :=
-                             New_Copy_Tree (Expression (Parent (Compon)));
-                        else
-                           Expr := Expression (Parent (Compon));
-                        end if;
+                        --  Note that we always copy the default expression,
+                        --  even when the association has a single choice, in
+                        --  order to create a proper association for the
+                        --  expanded aggregate.
 
-                     else
-                        Check_Non_Limited_Type;
+                        Expr := New_Copy_Tree (Expression (Parent (Compon)));
 
+                     else
                         if Present (Next (Selector_Name)) then
                            Expr := New_Copy_Tree (Expression (Assoc));
                         else
@@ -2429,6 +2453,31 @@ package body Sem_Aggr is
          return Expr;
       end Get_Value;
 
+      procedure Check_Non_Limited_Type (Expr : Node_Id);
+      --  Relax check to allow the default initialization of limited types.
+      --  For example:
+      --      record
+      --         C : Lim := (..., others => <>);
+      --      end record;
+
+      ----------------------------
+      -- Check_Non_Limited_Type --
+      ----------------------------
+
+      procedure Check_Non_Limited_Type (Expr : Node_Id) is
+      begin
+         if Is_Limited_Type (Etype (Expr))
+            and then Comes_From_Source (Expr)
+            and then not In_Instance_Body
+         then
+            if not OK_For_Limited_Init (Expr) then
+               Error_Msg_N
+                 ("initialization not allowed for limited types", N);
+               Explain_Limited_Type (Etype (Expr), Expr);
+            end if;
+         end if;
+      end Check_Non_Limited_Type;
+
       -----------------------
       -- Resolve_Aggr_Expr --
       -----------------------
@@ -2502,16 +2551,16 @@ package body Sem_Aggr is
 
             --  For each range in an array type where a discriminant has been
             --  replaced with the constraint, check that this range is within
-            --  the range of the base type. This checks is done in the
-            --  init proc for regular objects, but has to be done here for
+            --  the range of the base type. This checks is done in the init
+            --  proc for regular objects, but has to be done here for
             --  aggregates since no init proc is called for them.
 
             if Is_Array_Type (Expr_Type) then
                declare
-                  Index          : Node_Id := First_Index (Expr_Type);
-                  --  Range of the current constrained index in the array.
+                  Index : Node_Id;
+                  --  Range of the current constrained index in the array
 
-                  Orig_Index     : Node_Id := First_Index (Etype (Component));
+                  Orig_Index : Node_Id := First_Index (Etype (Component));
                   --  Range corresponding to the range Index above in the
                   --  original unconstrained record type. The bounds of this
                   --  range may be governed by discriminants.
@@ -2522,6 +2571,7 @@ package body Sem_Aggr is
                   --  range checks.
 
                begin
+                  Index := First_Index (Expr_Type);
                   while Present (Index) loop
                      if Depends_On_Discriminant (Orig_Index) then
                         Apply_Range_Check (Index, Etype (Unconstr_Index));
@@ -2551,6 +2601,7 @@ package body Sem_Aggr is
          end if;
 
          Analyze_And_Resolve (Expr, Expr_Type);
+         Check_Non_Limited_Type (Expr);
          Check_Non_Static_Context (Expr);
          Check_Unset_Reference (Expr);
 
@@ -2569,20 +2620,6 @@ package body Sem_Aggr is
          end if;
       end Resolve_Aggr_Expr;
 
-      --  Resolve_Record_Aggregate local variables
-
-      Assoc : Node_Id;
-      --  N_Component_Association node belonging to the input aggregate N
-
-      Expr            : Node_Id;
-      Positional_Expr : Node_Id;
-      Component       : Entity_Id;
-      Component_Elmt  : Elmt_Id;
-
-      Components : constant Elist_Id := New_Elmt_List;
-      --  Components is the list of the record components whose value must
-      --  be provided in the aggregate. This list does include discriminants.
-
    --  Start of processing for Resolve_Record_Aggregate
 
    begin
@@ -2595,7 +2632,7 @@ package body Sem_Aggr is
 
       --  STEP 1: abstract type and null record verification
 
-      if Is_Abstract (Typ) then
+      if Is_Abstract_Type (Typ) then
          Error_Msg_N ("type of aggregate cannot be abstract",  N);
       end if;
 
@@ -2693,7 +2730,9 @@ package body Sem_Aggr is
 
                --  Ada 2005 (AI-231)
 
-               if Ada_Version >= Ada_05 then
+               if Ada_Version >= Ada_05
+                 and then Nkind (Positional_Expr) = N_Null
+               then
                   Check_Can_Never_Be_Null (Discrim, Positional_Expr);
                end if;
 
@@ -2786,7 +2825,7 @@ package body Sem_Aggr is
                 Subtype_Indication  => Indic);
             Set_Parent (Subtyp_Decl, Parent (N));
 
-            --  Itypes must be analyzed with checks off (see itypes.ads).
+            --  Itypes must be analyzed with checks off (see itypes.ads)
 
             Analyze (Subtyp_Decl, Suppress => All_Checks);
 
@@ -2855,7 +2894,6 @@ package body Sem_Aggr is
 
             Parent_Typ  := Base_Type (Typ);
             while Parent_Typ /= Root_Typ loop
-
                Prepend_Elmt (Parent_Typ, To => Parent_Typ_List);
                Parent_Typ := Etype (Parent_Typ);
 
@@ -2880,7 +2918,7 @@ package body Sem_Aggr is
                end if;
             end loop;
 
-            --  Now collect components from all other ancestors.
+            --  Now collect components from all other ancestors
 
             Parent_Elmt := First_Elmt (Parent_Typ_List);
             while Present (Parent_Elmt) loop
@@ -2930,7 +2968,9 @@ package body Sem_Aggr is
 
          --  Ada 2005 (AI-231)
 
-         if Ada_Version >= Ada_05 then
+         if Ada_Version >= Ada_05
+           and then Nkind (Positional_Expr) = N_Null
+         then
             Check_Can_Never_Be_Null (Component, Positional_Expr);
          end if;
 
@@ -2954,23 +2994,144 @@ package body Sem_Aggr is
          Component := Node (Component_Elmt);
          Expr := Get_Value (Component, Component_Associations (N), True);
 
-         --  Ada 2005 (AI-287): Default initialized limited component are
-         --  passed to the expander, that will generate calls to the
-         --  corresponding IP.
+         --  Note: The previous call to Get_Value sets the value of the
+         --  variable Is_Box_Present
 
-         if Mbox_Present and then Is_Limited_Type (Etype (Component)) then
-            Add_Association
-              (Component   => Component,
-               Expr        => Empty,
-               Box_Present => True);
+         --  Ada 2005 (AI-287): Handle components with default initialization.
+         --  Note: This feature was originally added to Ada 2005 for limited
+         --  but it was finally allowed with any type.
 
-         --  Ada 2005 (AI-287): No value supplied for component
+         if Is_Box_Present then
+            declare
+               Is_Array_Subtype : constant Boolean :=
+                                    Ekind (Etype (Component)) =
+                                                           E_Array_Subtype;
 
-         elsif Mbox_Present and No (Expr) then
-            null;
+               Ctyp : Entity_Id;
+
+            begin
+               if Is_Array_Subtype then
+                  Ctyp := Component_Type (Base_Type (Etype (Component)));
+               else
+                  Ctyp := Etype (Component);
+               end if;
+
+               --  If there is a default expression for the aggregate, copy
+               --  it into a new association.
+
+               --  If the component has an initialization procedure (IP) we
+               --  pass the component to the expander, which will generate
+               --  the call to such IP.
+
+               --  If the component has discriminants, their values must
+               --  be taken from their subtype. This is indispensable for
+               --  constraints that are given by the current instance of an
+               --  enclosing type, to allow the expansion of the aggregate
+               --  to replace the reference to the current instance by the
+               --  target object of the aggregate.
+
+               if Present (Parent (Component))
+                 and then
+                   Nkind (Parent (Component)) = N_Component_Declaration
+                 and then Present (Expression (Parent (Component)))
+               then
+                  Expr :=
+                    New_Copy_Tree (Expression (Parent (Component)),
+                      New_Sloc => Sloc (N));
+
+                  Add_Association
+                    (Component => Component,
+                     Expr      => Expr);
+                  Set_Has_Self_Reference (N);
+
+               elsif Has_Non_Null_Base_Init_Proc (Ctyp)
+                 or else not Expander_Active
+               then
+                  if Is_Record_Type (Ctyp)
+                    and then Has_Discriminants (Ctyp)
+                  then
+                     --  We build a partially initialized aggregate with the
+                     --  values of the discriminants and box initialization
+                     --  for the rest.
+
+                     declare
+                        Loc        : constant Source_Ptr := Sloc (N);
+                        Discr_Elmt : Elmt_Id;
+                        Discr_Val  : Node_Id;
+                        Expr       : Node_Id;
+
+                     begin
+                        Expr := Make_Aggregate (Loc, New_List, New_List);
+
+                        Discr_Elmt :=
+                          First_Elmt (Discriminant_Constraint (Ctyp));
+                        while Present (Discr_Elmt) loop
+                           Discr_Val := Node (Discr_Elmt);
+                           Append
+                             (New_Copy_Tree (Discr_Val), Expressions (Expr));
+
+                           --  If the discriminant constraint is a current
+                           --  instance, mark the current aggregate so that
+                           --  the self-reference can be expanded later.
+
+                           if Nkind (Discr_Val) = N_Attribute_Reference
+                             and then Is_Entity_Name (Prefix (Discr_Val))
+                             and then Is_Type (Entity (Prefix (Discr_Val)))
+                             and then Etype (N) = Entity (Prefix (Discr_Val))
+                           then
+                              Set_Has_Self_Reference (N);
+                           end if;
+
+                           Next_Elmt (Discr_Elmt);
+                        end loop;
+
+                        Append
+                          (Make_Component_Association (Loc,
+                             Choices     =>
+                               New_List (Make_Others_Choice (Loc)),
+                             Expression  => Empty,
+                             Box_Present => True),
+                           Component_Associations (Expr));
+
+                        Add_Association
+                          (Component      => Component,
+                           Expr           => Expr);
+                     end;
+
+                  else
+                     Add_Association
+                       (Component      => Component,
+                        Expr           => Empty,
+                        Is_Box_Present => True);
+                  end if;
+
+               --  Otherwise we only need to resolve the expression if the
+               --  component has partially initialized values (required to
+               --  expand the corresponding assignments and run-time checks).
+
+               elsif Present (Expr)
+                 and then
+                   ((not Is_Array_Subtype
+                       and then Is_Partially_Initialized_Type (Component))
+                      or else
+                        (Is_Array_Subtype
+                           and then Is_Partially_Initialized_Type (Ctyp)))
+               then
+                  Resolve_Aggr_Expr (Expr, Component);
+               end if;
+            end;
 
          elsif No (Expr) then
-            Error_Msg_NE ("no value supplied for component &!", N, Component);
+
+            --  Ignore hidden components associated with the position of the
+            --  interface tags: these are initialized dynamically.
+
+            if Present (Related_Interface (Component)) then
+               null;
+            else
+               Error_Msg_NE
+                 ("no value supplied for component &!", N, Component);
+            end if;
 
          else
             Resolve_Aggr_Expr (Expr, Component);
@@ -2985,7 +3146,7 @@ package body Sem_Aggr is
          Selectr : Node_Id;
          --  Selector name
 
-         Typech  : Entity_Id;
+         Typech : Entity_Id;
          --  Type of first component in choice list
 
       begin
@@ -3001,10 +3162,10 @@ package body Sem_Aggr is
 
             if Nkind (Selectr) = N_Others_Choice then
 
-               --  Ada 2005 (AI-287): others choice may have expression or mbox
+               --  Ada 2005 (AI-287): others choice may have expression or box
 
                if No (Others_Etype)
-                  and then not Others_Mbox
+                  and then not Others_Box
                then
                   Error_Msg_N
                     ("OTHERS must represent at least one component", Selectr);
@@ -3022,12 +3183,34 @@ package body Sem_Aggr is
                end loop;
 
                --  If no association, this is not a legal component of
-               --  of the type in question,  except if this is an internal
-               --  component supplied by a previous expansion.
+               --  of the type in question, except if its association
+               --  is provided with a box.
 
                if No (New_Assoc) then
                   if Box_Present (Parent (Selectr)) then
-                     null;
+
+                     --  This may still be a bogus component with a box. Scan
+                     --  list of components to verify that a component with
+                     --  that name exists.
+
+                     declare
+                        C : Entity_Id;
+
+                     begin
+                        C := First_Component (Typ);
+                        while Present (C) loop
+                           if Chars (C) = Chars (Selectr) then
+                              exit;
+                           end if;
+
+                           Next_Component (C);
+                        end loop;
+
+                        if No (C) then
+                           Error_Msg_Node_2 := Typ;
+                           Error_Msg_N ("& is not a component of}", Selectr);
+                        end if;
+                     end;
 
                   elsif Chars (Selectr) /= Name_uTag
                     and then Chars (Selectr) /= Name_uParent
@@ -3035,9 +3218,7 @@ package body Sem_Aggr is
                   then
                      if not Has_Discriminants (Typ) then
                         Error_Msg_Node_2 := Typ;
-                        Error_Msg_N
-                          ("& is not a component of}",
-                            Selectr);
+                        Error_Msg_N ("& is not a component of}", Selectr);
                      else
                         Error_Msg_N
                           ("& is not a component of the aggregate subtype",
@@ -3083,19 +3264,45 @@ package body Sem_Aggr is
    -- Check_Can_Never_Be_Null --
    -----------------------------
 
-   procedure Check_Can_Never_Be_Null (N : Node_Id; Expr : Node_Id) is
+   procedure Check_Can_Never_Be_Null (Typ : Entity_Id; Expr : Node_Id) is
+      Comp_Typ : Entity_Id;
+
    begin
-      pragma Assert (Ada_Version >= Ada_05);
+      pragma Assert
+        (Ada_Version >= Ada_05
+          and then Present (Expr)
+          and then Nkind (Expr) = N_Null);
 
-      if Nkind (Expr) = N_Null
-        and then Can_Never_Be_Null (N)
-      then
-         Apply_Compile_Time_Constraint_Error
-           (N      => Expr,
-            Msg    => "(Ada 2005) NULL not allowed in"
-                       & " null-excluding components?",
-            Reason => CE_Null_Not_Allowed,
-            Rep    => False);
+      case Ekind (Typ) is
+         when E_Array_Type  =>
+            Comp_Typ := Component_Type (Typ);
+
+         when E_Component    |
+              E_Discriminant =>
+            Comp_Typ := Etype (Typ);
+
+         when others =>
+            return;
+      end case;
+
+      if Can_Never_Be_Null (Comp_Typ) then
+
+         --  Here we know we have a constraint error. Note that we do not use
+         --  Apply_Compile_Time_Constraint_Error here to the Expr, which might
+         --  seem the more natural approach. That's because in some cases the
+         --  components are rewritten, and the replacement would be missed.
+
+         Insert_Action
+           (Compile_Time_Constraint_Error
+              (Expr,
+               "(Ada 2005) NULL not allowed in null-excluding components?"),
+            Make_Raise_Constraint_Error (Sloc (Expr),
+              Reason => CE_Access_Check_Failed));
+
+         --  Set proper type for bogus component (why is this needed???)
+
+         Set_Etype    (Expr, Comp_Typ);
+         Set_Analyzed (Expr);
       end if;
    end Check_Can_Never_Be_Null;
 
@@ -3112,11 +3319,10 @@ package body Sem_Aggr is
 
    begin
       K := L;
-
       while K /= U loop
          T := Case_Table (K + 1);
-         J := K + 1;
 
+         J := K + 1;
          while J /= L
            and then Expr_Value (Case_Table (J - 1).Choice_Lo) >
                     Expr_Value (T.Choice_Lo)