OSDN Git Service

ada:
[pf3gnuchains/gcc-fork.git] / gcc / ada / freeze.adb
index ff32684..e807864 100644 (file)
@@ -6,18 +6,17 @@
 --                                                                          --
 --                                 B o d y                                  --
 --                                                                          --
---          Copyright (C) 1992-2010, Free Software Foundation, Inc.         --
+--          Copyright (C) 1992-2011, 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- --
 -- ware  Foundation;  either version 3,  or (at your option) any later ver- --
 -- sion.  GNAT is distributed in the hope that it will be useful, but WITH- --
 -- OUT ANY WARRANTY;  without even the  implied warranty of MERCHANTABILITY --
--- or FITNESS FOR A PARTICULAR PURPOSE.                                     --
---                                                                          --
--- You should have received a copy of the GNU General Public License along  --
--- with this program; see file COPYING3.  If not see                        --
--- <http://www.gnu.org/licenses/>.                                          --
+-- 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 COPYING3.  If not, go to --
+-- http://www.gnu.org/licenses for a complete copy of the license.          --
 --                                                                          --
 -- GNAT was originally developed  by the GNAT team at  New York University. --
 -- Extensive contributions were provided by Ada Core Technologies Inc.      --
@@ -101,10 +100,11 @@ package body Freeze is
 
    procedure Freeze_And_Append
      (Ent    : Entity_Id;
-      Loc    : Source_Ptr;
+      N      : Node_Id;
       Result : in out List_Id);
    --  Freezes Ent using Freeze_Entity, and appends the resulting list of
-   --  nodes to Result, modifying Result from No_List if necessary.
+   --  nodes to Result, modifying Result from No_List if necessary. N has
+   --  the same usage as in Freeze_Entity.
 
    procedure Freeze_Enumeration_Type (Typ : Entity_Id);
    --  Freeze enumeration type. The Esize field is set as processing
@@ -138,20 +138,20 @@ package body Freeze is
    procedure Process_Default_Expressions
      (E     : Entity_Id;
       After : in out Node_Id);
-   --  This procedure is called for each subprogram to complete processing
-   --  of default expressions at the point where all types are known to be
-   --  frozen. The expressions must be analyzed in full, to make sure that
-   --  all error processing is done (they have only been pre-analyzed). If
-   --  the expression is not an entity or literal, its analysis may generate
-   --  code which must not be executed. In that case we build a function
-   --  body to hold that code. This wrapper function serves no other purpose
-   --  (it used to be called to evaluate the default, but now the default is
-   --  inlined at each point of call).
+   --  This procedure is called for each subprogram to complete processing of
+   --  default expressions at the point where all types are known to be frozen.
+   --  The expressions must be analyzed in full, to make sure that all error
+   --  processing is done (they have only been pre-analyzed). If the expression
+   --  is not an entity or literal, its analysis may generate code which must
+   --  not be executed. In that case we build a function body to hold that
+   --  code. This wrapper function serves no other purpose (it used to be
+   --  called to evaluate the default, but now the default is inlined at each
+   --  point of call).
 
    procedure Set_Component_Alignment_If_Not_Set (Typ : Entity_Id);
-   --  Typ is a record or array type that is being frozen. This routine
-   --  sets the default component alignment from the scope stack values
-   --  if the alignment is otherwise not specified.
+   --  Typ is a record or array type that is being frozen. This routine sets
+   --  the default component alignment from the scope stack values if the
+   --  alignment is otherwise not specified.
 
    procedure Check_Debug_Info_Needed (T : Entity_Id);
    --  As each entity is frozen, this routine is called to deal with the
@@ -162,9 +162,9 @@ package body Freeze is
    --  subsidiary entities have the flag set as required.
 
    procedure Undelay_Type (T : Entity_Id);
-   --  T is a type of a component that we know to be an Itype.
-   --  We don't want this to have a Freeze_Node, so ensure it doesn't.
-   --  Do the same for any Full_View or Corresponding_Record_Type.
+   --  T is a type of a component that we know to be an Itype. We don't want
+   --  this to have a Freeze_Node, so ensure it doesn't. Do the same for any
+   --  Full_View or Corresponding_Record_Type.
 
    procedure Warn_Overlay
      (Expr : Node_Id;
@@ -233,7 +233,7 @@ package body Freeze is
           (not In_Same_Source_Unit (Renamed_Subp, Ent)
             or else Sloc (Renamed_Subp) < Sloc (Ent))
 
-        --  We can make the renaming entity intrisic if the renamed function
+        --  We can make the renaming entity intrinsic if the renamed function
         --  has an interface name, or if it is one of the shift/rotate
         --  operations known to the compiler.
 
@@ -361,10 +361,13 @@ package body Freeze is
 
       --  For simple renamings, subsequent calls can be expanded directly as
       --  calls to the renamed entity. The body must be generated in any case
-      --  for calls that may appear elsewhere.
+      --  for calls that may appear elsewhere. This is not done in the case
+      --  where the subprogram is an instantiation because the actual proper
+      --  body has not been built yet.
 
       if Ekind_In (Old_S, E_Function, E_Procedure)
         and then Nkind (Decl) = N_Subprogram_Declaration
+        and then not Is_Generic_Instance (Old_S)
       then
          Set_Body_To_Inline (Decl, Old_S);
       end if;
@@ -623,13 +626,6 @@ package body Freeze is
          if S > 32 then
             return;
 
-         --  Don't bother if alignment clause with a value other than 1 is
-         --  present, because size may be padded up to meet back end alignment
-         --  requirements, and only the back end knows the rules!
-
-         elsif Known_Alignment (T) and then Alignment (T) /= 1 then
-            return;
-
          --  Check for bad size clause given
 
          elsif Has_Size_Clause (T) then
@@ -638,21 +634,12 @@ package body Freeze is
                Error_Msg_NE
                  ("size for& too small, minimum allowed is ^",
                   Size_Clause (T), T);
-
-            elsif Unknown_Esize (T) then
-               Set_Esize (T, S);
             end if;
 
-         --  Set sizes if not set already
+         --  Set size if not set already
 
-         else
-            if Unknown_Esize (T) then
-               Set_Esize (T, S);
-            end if;
-
-            if Unknown_RM_Size (T) then
-               Set_RM_Size (T, S);
-            end if;
+         elsif Unknown_RM_Size (T) then
+            Set_RM_Size (T, S);
          end if;
       end Set_Small_Size;
 
@@ -783,7 +770,7 @@ package body Freeze is
                return False;
 
             --  A subtype of a variant record must not have non-static
-            --  discriminanted components.
+            --  discriminated components.
 
             elsif T /= Base_Type (T)
               and then not Static_Discriminated_Components (T)
@@ -836,7 +823,7 @@ package body Freeze is
                   if not Is_Constrained (T)
                     and then
                       No (Discriminant_Default_Value (First_Discriminant (T)))
-                    and then Unknown_Esize (T)
+                    and then Unknown_RM_Size (T)
                   then
                      return False;
                   end if;
@@ -1058,7 +1045,6 @@ package body Freeze is
          end if;
 
          Comp := First_Component (E);
-
          while Present (Comp) loop
             if not Is_Type (Comp)
               and then (Strict_Alignment (Etype (Comp))
@@ -1209,7 +1195,6 @@ package body Freeze is
    --  as they are generated.
 
    procedure Freeze_All (From : Entity_Id; After : in out Node_Id) is
-      Loc   : constant Source_Ptr := Sloc (After);
       E     : Entity_Id;
       Decl  : Node_Id;
 
@@ -1277,6 +1262,13 @@ package body Freeze is
 
                End_Package_Scope (E);
 
+               if Is_Generic_Instance (E)
+                 and then Has_Delayed_Freeze (E)
+               then
+                  Set_Has_Delayed_Freeze (E, False);
+                  Expand_N_Package_Declaration (Unit_Declaration_Node (E));
+               end if;
+
             elsif Ekind (E) in Task_Kind
               and then
                 (Nkind (Parent (E)) = N_Task_Type_Declaration
@@ -1305,14 +1297,14 @@ package body Freeze is
                   Subp : Entity_Id;
 
                begin
-                  Prim  := First_Elmt (Prim_List);
+                  Prim := First_Elmt (Prim_List);
                   while Present (Prim) loop
                      Subp := Node (Prim);
 
                      if Comes_From_Source (Subp)
                        and then not Is_Frozen (Subp)
                      then
-                        Flist := Freeze_Entity (Subp, Loc);
+                        Flist := Freeze_Entity (Subp, After);
                         Process_Flist;
                      end if;
 
@@ -1322,8 +1314,30 @@ package body Freeze is
             end if;
 
             if not Is_Frozen (E) then
-               Flist := Freeze_Entity (E, Loc);
+               Flist := Freeze_Entity (E, After);
                Process_Flist;
+
+            --  If already frozen, and there are delayed aspects, this is where
+            --  we do the visibility check for these aspects (see Sem_Ch13 spec
+            --  for a description of how we handle aspect visibility).
+
+            elsif Has_Delayed_Aspects (E) then
+               declare
+                  Ritem : Node_Id;
+
+               begin
+                  Ritem := First_Rep_Item (E);
+                  while Present (Ritem) loop
+                     if Nkind (Ritem) = N_Aspect_Specification
+                       and then Entity (Ritem) = E
+                       and then Is_Delayed_Aspect (Ritem)
+                     then
+                        Check_Aspect_At_End_Of_Declarations (Ritem);
+                     end if;
+
+                     Ritem := Next_Rep_Item (Ritem);
+                  end loop;
+               end;
             end if;
 
             --  If an incomplete type is still not frozen, this may be a
@@ -1428,13 +1442,24 @@ package body Freeze is
                end loop;
             end;
 
+         --  We add finalization masters to access types whose designated types
+         --  require finalization. This is normally done when freezing the
+         --  type, but this misses recursive type definitions where the later
+         --  members of the recursion introduce controlled components (such as
+         --  can happen when incomplete types are involved), as well cases
+         --  where a component type is private and the controlled full type
+         --  occurs after the access type is frozen. Cases that don't need a
+         --  finalization master are generic formal types (the actual type will
+         --  have it) and types with Java and CIL conventions, since those are
+         --  used for API bindings. (Are there any other cases that should be
+         --  excluded here???)
+
          elsif Is_Access_Type (E)
            and then Comes_From_Source (E)
-           and then Ekind (Directly_Designated_Type (E)) = E_Incomplete_Type
+           and then not Is_Generic_Type (E)
            and then Needs_Finalization (Designated_Type (E))
-           and then No (Associated_Final_Chain (E))
          then
-            Build_Final_List (Parent (E), E);
+            Build_Finalization_Master (E);
          end if;
 
          Next_Entity (E);
@@ -1447,10 +1472,10 @@ package body Freeze is
 
    procedure Freeze_And_Append
      (Ent    : Entity_Id;
-      Loc    : Source_Ptr;
+      N      : Node_Id;
       Result : in out List_Id)
    is
-      L : constant List_Id := Freeze_Entity (Ent, Loc);
+      L : constant List_Id := Freeze_Entity (Ent, N);
    begin
       if Is_Non_Empty_List (L) then
          if Result = No_List then
@@ -1466,7 +1491,7 @@ package body Freeze is
    -------------------
 
    procedure Freeze_Before (N : Node_Id; T : Entity_Id) is
-      Freeze_Nodes : constant List_Id := Freeze_Entity (T, Sloc (N));
+      Freeze_Nodes : constant List_Id := Freeze_Entity (T, N);
    begin
       if Is_Non_Empty_List (Freeze_Nodes) then
          Insert_Actions (N, Freeze_Nodes);
@@ -1477,18 +1502,24 @@ package body Freeze is
    -- Freeze_Entity --
    -------------------
 
-   function Freeze_Entity (E : Entity_Id; Loc : Source_Ptr) return List_Id is
+   function Freeze_Entity (E : Entity_Id; N : Node_Id) return List_Id is
+      Loc    : constant Source_Ptr := Sloc (N);
       Test_E : Entity_Id := E;
       Comp   : Entity_Id;
       F_Node : Node_Id;
-      Result : List_Id;
       Indx   : Node_Id;
       Formal : Entity_Id;
       Atype  : Entity_Id;
 
+      Result : List_Id := No_List;
+      --  List of freezing actions, left at No_List if none
+
       Has_Default_Initialization : Boolean := False;
       --  This flag gets set to true for a variable with default initialization
 
+      procedure Add_To_Result (N : Node_Id);
+      --  N is a freezing action to be appended to the Result
+
       procedure Check_Current_Instance (Comp_Decl : Node_Id);
       --  Check that an Access or Unchecked_Access attribute with a prefix
       --  which is the current instance type can only be applied when the type
@@ -1507,6 +1538,19 @@ package body Freeze is
       --  Freeze each component, handle some representation clauses, and freeze
       --  primitive operations if this is a tagged type.
 
+      -------------------
+      -- Add_To_Result --
+      -------------------
+
+      procedure Add_To_Result (N : Node_Id) is
+      begin
+         if No (Result) then
+            Result := New_List (N);
+         else
+            Append (N, Result);
+         end if;
+      end Add_To_Result;
+
       ----------------------------
       -- After_Last_Declaration --
       ----------------------------
@@ -1577,7 +1621,7 @@ package body Freeze is
          --  either a tagged type, or a limited record.
 
          if Is_Limited_Type (Rec_Type)
-           and then (Ada_Version < Ada_05 or else Is_Tagged_Type (Rec_Type))
+           and then (Ada_Version < Ada_2005 or else Is_Tagged_Type (Rec_Type))
          then
             return;
 
@@ -1748,12 +1792,7 @@ package body Freeze is
                then
                   IR := Make_Itype_Reference (Sloc (Comp));
                   Set_Itype (IR, Desig);
-
-                  if No (Result) then
-                     Result := New_List (IR);
-                  else
-                     Append (IR, Result);
-                  end if;
+                  Add_To_Result (IR);
                end if;
 
             elsif Ekind (Typ) = E_Anonymous_Access_Subprogram_Type
@@ -1766,40 +1805,6 @@ package body Freeze is
       --  Start of processing for Freeze_Record_Type
 
       begin
-         --  If this is a subtype of a controlled type, declared without a
-         --  constraint, the _controller may not appear in the component list
-         --  if the parent was not frozen at the point of subtype declaration.
-         --  Inherit the _controller component now.
-
-         if Rec /= Base_Type (Rec)
-           and then Has_Controlled_Component (Rec)
-         then
-            if Nkind (Parent (Rec)) = N_Subtype_Declaration
-              and then Is_Entity_Name (Subtype_Indication (Parent (Rec)))
-            then
-               Set_First_Entity (Rec, First_Entity (Base_Type (Rec)));
-
-            --  If this is an internal type without a declaration, as for
-            --  record component, the base type may not yet be frozen, and its
-            --  controller has not been created. Add an explicit freeze node
-            --  for the itype, so it will be frozen after the base type. This
-            --  freeze node is used to communicate with the expander, in order
-            --  to create the controller for the enclosing record, and it is
-            --  deleted afterwards (see exp_ch3). It must not be created when
-            --  expansion is off, because it might appear in the wrong context
-            --  for the back end.
-
-            elsif Is_Itype (Rec)
-              and then Has_Delayed_Freeze (Base_Type (Rec))
-              and then
-                Nkind (Associated_Node_For_Itype (Rec)) =
-                                                     N_Component_Declaration
-              and then Expander_Active
-            then
-               Ensure_Freeze_Node (Rec);
-            end if;
-         end if;
-
          --  Freeze components and embedded subtypes
 
          Comp := First_Entity (Rec);
@@ -1830,7 +1835,7 @@ package body Freeze is
                      Undelay_Type (Etype (Comp));
                   end if;
 
-                  Freeze_And_Append (Etype (Comp), Loc, Result);
+                  Freeze_And_Append (Etype (Comp), N, Result);
 
                   --  Check for error of component clause given for variable
                   --  sized type. We have to delay this test till this point,
@@ -1838,12 +1843,18 @@ package body Freeze is
                   --  if it is variable length. We omit this test in a generic
                   --  context, it will be applied at instantiation time.
 
+                  --  We also omit this test in CodePeer mode, since we do not
+                  --  have sufficient info on size and representation clauses.
+
                   if Present (CC) then
                      Placed_Component := True;
 
                      if Inside_A_Generic then
                         null;
 
+                     elsif CodePeer_Mode then
+                        null;
+
                      elsif not
                        Size_Known_At_Compile_Time
                          (Underlying_Type (Etype (Comp)))
@@ -1989,13 +2000,13 @@ package body Freeze is
                      then
                         if Is_Entity_Name (Expression (Alloc)) then
                            Freeze_And_Append
-                             (Entity (Expression (Alloc)), Loc, Result);
+                             (Entity (Expression (Alloc)), N, Result);
                         elsif
                           Nkind (Expression (Alloc)) = N_Subtype_Indication
                         then
                            Freeze_And_Append
                             (Entity (Subtype_Mark (Expression (Alloc))),
-                              Loc, Result);
+                             N, Result);
                         end if;
 
                      elsif Is_Itype (Designated_Type (Etype (Comp))) then
@@ -2003,7 +2014,7 @@ package body Freeze is
 
                      else
                         Freeze_And_Append
-                          (Designated_Type (Etype (Comp)), Loc, Result);
+                          (Designated_Type (Etype (Comp)), N, Result);
                      end if;
                   end if;
                end;
@@ -2024,14 +2035,14 @@ package body Freeze is
             then
                Freeze_And_Append
                  (Designated_Type
-                   (Component_Type (Etype (Comp))), Loc, Result);
+                   (Component_Type (Etype (Comp))), N, Result);
             end if;
 
             Prev := Comp;
             Next_Entity (Comp);
          end loop;
 
-         --  Deal with pragma Bit_Order setting non-standard bit order
+         --  Deal with Bit_Order aspect specifying a non-default bit order
 
          if Reverse_Bit_Order (Rec) and then Base_Type (Rec) = Rec then
             if not Placed_Component then
@@ -2062,9 +2073,7 @@ package body Freeze is
 
          --  Set OK_To_Reorder_Components depending on debug flags
 
-         if Rec = Base_Type (Rec)
-           and then Convention (Rec) = Convention_Ada
-         then
+         if Is_Base_Type (Rec) and then Convention (Rec) = Convention_Ada then
             if (Has_Discriminants (Rec) and then Debug_Flag_Dot_V)
                   or else
                (not Has_Discriminants (Rec) and then Debug_Flag_Dot_R)
@@ -2111,8 +2120,7 @@ package body Freeze is
 
          if Ekind (Rec) = E_Record_Type then
             if Present (Corresponding_Remote_Type (Rec)) then
-               Freeze_And_Append
-                 (Corresponding_Remote_Type (Rec), Loc, Result);
+               Freeze_And_Append (Corresponding_Remote_Type (Rec), N, Result);
             end if;
 
             Comp := First_Component (Rec);
@@ -2163,7 +2171,6 @@ package body Freeze is
 
          if Is_First_Subtype (Rec) then
             Comp := First_Component (Rec);
-
             while Present (Comp) loop
                if Present (Component_Clause (Comp))
                  and then (Is_Fixed_Point_Type (Etype (Comp))
@@ -2241,19 +2248,20 @@ package body Freeze is
            --  less than the sum of the object sizes (no point in packing if
            --  this is not the case).
 
-           and then Esize (Rec) < Scalar_Component_Total_Esize
+           and then RM_Size (Rec) < Scalar_Component_Total_Esize
 
            --  And the total RM size cannot be greater than the specified size
            --  since otherwise packing will not get us where we have to be!
 
-           and then Esize (Rec) >= Scalar_Component_Total_RM_Size
+           and then RM_Size (Rec) >= Scalar_Component_Total_RM_Size
 
-           --  Never do implicit packing in CodePeer mode since we don't do
-           --  any packing in this mode, since this generates over-complex
-           --  code that confuses CodePeer, and in general, CodePeer does not
-           --  care about the internal representation of objects.
+           --  Never do implicit packing in CodePeer or Alfa modes since
+           --  we don't do any packing in these modes, since this generates
+           --  over-complex code that confuses static analysis, and in
+           --  general, neither CodePeer not GNATprove care about the
+           --  internal representation of objects.
 
-           and then not CodePeer_Mode
+           and then not (CodePeer_Mode or Alfa_Mode)
          then
             --  If implicit packing enabled, do it
 
@@ -2303,6 +2311,16 @@ package body Freeze is
       elsif Inside_A_Generic and then External_Ref_In_Generic (Test_E) then
          return No_List;
 
+      --  AI05-0213: A formal incomplete type does not freeze the actual. In
+      --  the instance, the same applies to the subtype renaming the actual.
+
+      elsif Is_Private_Type (E)
+        and then Is_Generic_Actual_Type (E)
+        and then No (Full_View (Base_Type (E)))
+        and then Ada_Version >= Ada_2012
+      then
+         return No_List;
+
       --  Do not freeze a global entity within an inner scope created during
       --  expansion. A call to subprogram E within some internal procedure
       --  (a stream attribute for example) might require freezing E, but the
@@ -2322,10 +2340,10 @@ package body Freeze is
         and then Ekind (Test_E) /= E_Constant
       then
          declare
-            S : Entity_Id := Current_Scope;
+            S : Entity_Id;
 
          begin
-
+            S := Current_Scope;
             while Present (S) loop
                if Is_Overloadable (S) then
                   if Comes_From_Source (S)
@@ -2356,9 +2374,10 @@ package body Freeze is
         and then Present (Scope (Test_E))
       then
          declare
-            S : Entity_Id := Scope (Test_E);
+            S : Entity_Id;
 
          begin
+            S := Scope (Test_E);
             while Present (S) loop
                if Is_Generic_Instance (S) then
                   exit;
@@ -2373,9 +2392,43 @@ package body Freeze is
          end;
       end if;
 
+      --  Deal with delayed aspect specifications. The analysis of the aspect
+      --  is required to be delayed to the freeze point, so we evaluate the
+      --  pragma or attribute definition clause in the tree at this point.
+
+      if Has_Delayed_Aspects (E) then
+         declare
+            Ritem : Node_Id;
+            Aitem : Node_Id;
+
+         begin
+            --  Look for aspect specification entries for this entity
+
+            Ritem := First_Rep_Item (E);
+            while Present (Ritem) loop
+               if Nkind (Ritem) = N_Aspect_Specification
+                 and then Entity (Ritem) = E
+                 and then Is_Delayed_Aspect (Ritem)
+                 and then Scope (E) = Current_Scope
+               then
+                  Aitem := Aspect_Rep_Item (Ritem);
+
+                  --  Skip if this is an aspect with no corresponding pragma
+                  --  or attribute definition node (such as Default_Value).
+
+                  if Present (Aitem) then
+                     Set_Parent (Aitem, Ritem);
+                     Analyze (Aitem);
+                  end if;
+               end if;
+
+               Next_Rep_Item (Ritem);
+            end loop;
+         end;
+      end if;
+
       --  Here to freeze the entity
 
-      Result := No_List;
       Set_Is_Frozen (E);
 
       --  Case of entity being frozen is other than a type
@@ -2409,8 +2462,7 @@ package body Freeze is
            and then Nkind (Parent (E)) = N_Object_Declaration
            and then Present (Expression (Parent (E)))
            and then Nkind (Expression (Parent (E))) = N_Aggregate
-           and then
-             Is_Atomic_Aggregate (Expression (Parent (E)), Etype (E))
+           and then Is_Atomic_Aggregate (Expression (Parent (E)), Etype (E))
          then
             null;
          end if;
@@ -2434,7 +2486,19 @@ package body Freeze is
                   Formal := First_Formal (E);
                   while Present (Formal) loop
                      F_Type := Etype (Formal);
-                     Freeze_And_Append (F_Type, Loc, Result);
+
+                     --  AI05-0151 : incomplete types can appear in a profile.
+                     --  By the time the entity is frozen, the full view must
+                     --  be available, unless it is a limited view.
+
+                     if Is_Incomplete_Type (F_Type)
+                       and then Present (Full_View (F_Type))
+                     then
+                        F_Type := Full_View (F_Type);
+                        Set_Etype (Formal, F_Type);
+                     end if;
+
+                     Freeze_And_Append (F_Type, N, Result);
 
                      if Is_Private_Type (F_Type)
                        and then Is_Private_Type (Base_Type (F_Type))
@@ -2590,7 +2654,7 @@ package body Freeze is
                         if Is_Itype (Etype (Formal))
                           and then Ekind (F_Type) = E_Subprogram_Type
                         then
-                           Freeze_And_Append (F_Type, Loc, Result);
+                           Freeze_And_Append (F_Type, N, Result);
                         end if;
                      end if;
 
@@ -2604,7 +2668,18 @@ package body Freeze is
                      --  Freeze return type
 
                      R_Type := Etype (E);
-                     Freeze_And_Append (R_Type, Loc, Result);
+
+                     --  AI05-0151: the return type may have been incomplete
+                     --  at the point of declaration.
+
+                     if Ekind (R_Type) = E_Incomplete_Type
+                       and then Present (Full_View (R_Type))
+                     then
+                        R_Type := Full_View (R_Type);
+                        Set_Etype (E, R_Type);
+                     end if;
+
+                     Freeze_And_Append (R_Type, N, Result);
 
                      --  Check suspicious return type for C function
 
@@ -2678,7 +2753,7 @@ package body Freeze is
                         end if;
                      end if;
 
-                     --  Give warning for suspicous return of a result of an
+                     --  Give warning for suspicious return of a result of an
                      --  unconstrained array type in a foreign convention
                      --  function.
 
@@ -2690,7 +2765,8 @@ package body Freeze is
                        and then not Is_Constrained (R_Type)
 
                        --  Exclude imported routines, the warning does not
-                       --  belong on the import, but on the routine definition.
+                       --  belong on the import, but rather on the routine
+                       --  definition.
 
                        and then not Is_Imported (E)
 
@@ -2717,7 +2793,7 @@ package body Freeze is
             --  Must freeze its parent first if it is a derived subprogram
 
             if Present (Alias (E)) then
-               Freeze_And_Append (Alias (E), Loc, Result);
+               Freeze_And_Append (Alias (E), N, Result);
             end if;
 
             --  We don't freeze internal subprograms, because we don't normally
@@ -2741,7 +2817,7 @@ package body Freeze is
             if Present (Etype (E))
               and then Ekind (E) /= E_Generic_Function
             then
-               Freeze_And_Append (Etype (E), Loc, Result);
+               Freeze_And_Append (Etype (E), N, Result);
             end if;
 
             --  Special processing for objects created by object declaration
@@ -2753,7 +2829,7 @@ package body Freeze is
 
                --  Note: we inhibit this check for objects that do not come
                --  from source because there is at least one case (the
-               --  expansion of x'class'input where x is abstract) where we
+               --  expansion of x'Class'Input where x is abstract) where we
                --  legitimately generate an abstract object.
 
                if Is_Abstract_Type (Etype (E))
@@ -2802,7 +2878,7 @@ package body Freeze is
                    ((Has_Non_Null_Base_Init_Proc (Etype (E))
                       and then not No_Initialization (Declaration_Node (E))
                       and then not Is_Value_Type (Etype (E))
-                      and then not Suppress_Init_Proc (Etype (E)))
+                      and then not Initialization_Suppressed (Etype (E)))
                     or else
                       (Needs_Simple_Initialization (Etype (E))
                         and then not Is_Internal (E)))
@@ -2935,7 +3011,7 @@ package body Freeze is
       else
          --  We used to check here that a full type must have preelaborable
          --  initialization if it completes a private type specified with
-         --  pragma Preelaborable_Intialization, but that missed cases where
+         --  pragma Preelaborable_Initialization, but that missed cases where
          --  the types occur within a generic package, since the freezing
          --  that occurs within a containing scope generally skips traversal
          --  of a generic unit's declarations (those will be frozen within
@@ -2990,16 +3066,16 @@ package body Freeze is
                   --  action that causes stuff to be inherited).
 
                   if Present (Size_Clause (E))
-                    and then Known_Static_Esize (E)
+                    and then Known_Static_RM_Size (E)
                     and then not Is_Packed (E)
                     and then not Has_Pragma_Pack (E)
                     and then Number_Dimensions (E) = 1
                     and then not Has_Component_Size_Clause (E)
-                    and then Known_Static_Esize (Ctyp)
+                    and then Known_Static_RM_Size (Ctyp)
                     and then not Is_Limited_Composite (E)
                     and then not Is_Packed (Root_Type (E))
                     and then not Has_Component_Size_Clause (Root_Type (E))
-                    and then not CodePeer_Mode
+                    and then not (CodePeer_Mode or Alfa_Mode)
                   then
                      Get_Index_Bounds (First_Index (E), Lo, Hi);
 
@@ -3071,25 +3147,38 @@ package body Freeze is
             end if;
 
             --  If ancestor subtype present, freeze that first. Note that this
-            --  will also get the base type frozen.
+            --  will also get the base type frozen. Need RM reference ???
 
             Atype := Ancestor_Subtype (E);
 
             if Present (Atype) then
-               Freeze_And_Append (Atype, Loc, Result);
+               Freeze_And_Append (Atype, N, Result);
+
+            --  No ancestor subtype present
+
+            else
+               --  See if we have a nearest ancestor that has a predicate.
+               --  That catches the case of derived type with a predicate.
+               --  Need RM reference here ???
+
+               Atype := Nearest_Ancestor (E);
+
+               if Present (Atype) and then Has_Predicates (Atype) then
+                  Freeze_And_Append (Atype, N, Result);
+               end if;
 
-            --  Otherwise freeze the base type of the entity before freezing
-            --  the entity itself (RM 13.14(15)).
+               --  Freeze base type before freezing the entity (RM 13.14(15))
 
-            elsif E /= Base_Type (E) then
-               Freeze_And_Append (Base_Type (E), Loc, Result);
+               if E /= Base_Type (E) then
+                  Freeze_And_Append (Base_Type (E), N, Result);
+               end if;
             end if;
 
          --  For a derived type, freeze its parent type first (RM 13.14(15))
 
          elsif Is_Derived_Type (E) then
-            Freeze_And_Append (Etype (E), Loc, Result);
-            Freeze_And_Append (First_Subtype (Etype (E)), Loc, Result);
+            Freeze_And_Append (Etype (E), N, Result);
+            Freeze_And_Append (First_Subtype (Etype (E)), N, Result);
          end if;
 
          --  For array type, freeze index types and component type first
@@ -3097,18 +3186,20 @@ package body Freeze is
 
          if Is_Array_Type (E) then
             declare
-               Ctyp : constant Entity_Id := Component_Type (E);
+               FS     : constant Entity_Id := First_Subtype (E);
+               Ctyp   : constant Entity_Id := Component_Type (E);
+               Clause : Entity_Id;
 
                Non_Standard_Enum : Boolean := False;
                --  Set true if any of the index types is an enumeration type
                --  with a non-standard representation.
 
             begin
-               Freeze_And_Append (Ctyp, Loc, Result);
+               Freeze_And_Append (Ctyp, N, Result);
 
                Indx := First_Index (E);
                while Present (Indx) loop
-                  Freeze_And_Append (Etype (Indx), Loc, Result);
+                  Freeze_And_Append (Etype (Indx), N, Result);
 
                   if Is_Enumeration_Type (Etype (Indx))
                     and then Has_Non_Standard_Rep (Etype (Indx))
@@ -3150,8 +3241,8 @@ package body Freeze is
 
                   begin
                      if (Is_Packed (E) or else Has_Pragma_Pack (E))
-                       and then not Has_Atomic_Components (E)
                        and then Known_Static_RM_Size (Ctyp)
+                       and then not Has_Component_Size_Clause (E)
                      then
                         Csiz := UI_Max (RM_Size (Ctyp), 1);
 
@@ -3213,6 +3304,7 @@ package body Freeze is
 
                            if Present (Comp_Size_C)
                              and then Has_Pragma_Pack (Ent)
+                             and then Warn_On_Redundant_Constructs
                            then
                               Error_Msg_Sloc := Sloc (Comp_Size_C);
                               Error_Msg_NE
@@ -3221,6 +3313,8 @@ package body Freeze is
                               Error_Msg_N
                                 ("\?explicit component size given#!",
                                  Pack_Pragma);
+                              Set_Is_Packed (Base_Type (Ent), False);
+                              Set_Is_Bit_Packed_Array (Base_Type (Ent), False);
                            end if;
 
                            --  Set component size if not already set by a
@@ -3277,19 +3371,151 @@ package body Freeze is
                               --  a representation characteristic, and this
                               --  request may be ignored.
 
-                              Set_Is_Packed (Base_Type (E), False);
+                              Set_Is_Packed           (Base_Type (E), False);
+                              Set_Is_Bit_Packed_Array (Base_Type (E), False);
+
+                              if Known_Static_Esize (Component_Type (E))
+                                and then Esize (Component_Type (E)) = Csiz
+                              then
+                                 Set_Has_Non_Standard_Rep
+                                   (Base_Type (E), False);
+                              end if;
 
-                              --  In all other cases, packing is indeed needed
+                           --  In all other cases, packing is indeed needed
 
                            else
-                              Set_Has_Non_Standard_Rep (Base_Type (E));
-                              Set_Is_Bit_Packed_Array  (Base_Type (E));
-                              Set_Is_Packed            (Base_Type (E));
+                              Set_Has_Non_Standard_Rep (Base_Type (E), True);
+                              Set_Is_Bit_Packed_Array  (Base_Type (E), True);
+                              Set_Is_Packed            (Base_Type (E), True);
                            end if;
                         end;
                      end if;
                   end;
 
+                  --  Check for Atomic_Components or Aliased with unsuitable
+                  --  packing or explicit component size clause given.
+
+                  if (Has_Atomic_Components (E)
+                       or else Has_Aliased_Components (E))
+                    and then (Has_Component_Size_Clause (E)
+                               or else Is_Packed (E))
+                  then
+                     Alias_Atomic_Check : declare
+
+                        procedure Complain_CS (T : String);
+                        --  Outputs error messages for incorrect CS clause or
+                        --  pragma Pack for aliased or atomic components (T is
+                        --  "aliased" or "atomic");
+
+                        -----------------
+                        -- Complain_CS --
+                        -----------------
+
+                        procedure Complain_CS (T : String) is
+                        begin
+                           if Has_Component_Size_Clause (E) then
+                              Clause :=
+                                Get_Attribute_Definition_Clause
+                                  (FS, Attribute_Component_Size);
+
+                              if Known_Static_Esize (Ctyp) then
+                                 Error_Msg_N
+                                   ("incorrect component size for "
+                                    & T & " components", Clause);
+                                 Error_Msg_Uint_1 := Esize (Ctyp);
+                                 Error_Msg_N
+                                   ("\only allowed value is^", Clause);
+
+                              else
+                                 Error_Msg_N
+                                   ("component size cannot be given for "
+                                    & T & " components", Clause);
+                              end if;
+
+                           else
+                              Error_Msg_N
+                                ("cannot pack " & T & " components",
+                                 Get_Rep_Pragma (FS, Name_Pack));
+                           end if;
+
+                           return;
+                        end Complain_CS;
+
+                     --  Start of processing for Alias_Atomic_Check
+
+                     begin
+
+                        --  If object size of component type isn't known, we
+                        --  cannot be sure so we defer to the back end.
+
+                        if not Known_Static_Esize (Ctyp) then
+                           null;
+
+                        --  Case where component size has no effect. First
+                        --  check for object size of component type multiple
+                        --  of the storage unit size.
+
+                        elsif Esize (Ctyp) mod System_Storage_Unit = 0
+
+                          --  OK in both packing case and component size case
+                          --  if RM size is known and static and the same as
+                          --  the object size.
+
+                          and then
+                            ((Known_Static_RM_Size (Ctyp)
+                               and then Esize (Ctyp) = RM_Size (Ctyp))
+
+                             --  Or if we have an explicit component size
+                             --  clause and the component size and object size
+                             --  are equal.
+
+                             or else
+                                 (Has_Component_Size_Clause (E)
+                                 and then Component_Size (E) = Esize (Ctyp)))
+                        then
+                           null;
+
+                        elsif Has_Aliased_Components (E)
+                          or else Is_Aliased (Ctyp)
+                        then
+                           Complain_CS ("aliased");
+
+                        elsif Has_Atomic_Components (E)
+                          or else Is_Atomic (Ctyp)
+                        then
+                           Complain_CS ("atomic");
+                        end if;
+                     end Alias_Atomic_Check;
+                  end if;
+
+                  --  Warn for case of atomic type
+
+                  Clause := Get_Rep_Pragma (FS, Name_Atomic);
+
+                  if Present (Clause)
+                    and then not Addressable (Component_Size (FS))
+                  then
+                     Error_Msg_NE
+                       ("non-atomic components of type& may not be "
+                        & "accessible by separate tasks?", Clause, E);
+
+                     if Has_Component_Size_Clause (E) then
+                        Error_Msg_Sloc :=
+                          Sloc
+                            (Get_Attribute_Definition_Clause
+                                 (FS, Attribute_Component_Size));
+                        Error_Msg_N
+                          ("\because of component size clause#?",
+                           Clause);
+
+                     elsif Has_Pragma_Pack (E) then
+                        Error_Msg_Sloc :=
+                          Sloc (Get_Rep_Pragma (FS, Name_Pack));
+                        Error_Msg_N
+                          ("\because of pragma Pack#?", Clause);
+                     end if;
+                  end if;
+
                --  Processing that is done only for subtypes
 
                else
@@ -3324,9 +3550,9 @@ package body Freeze is
                   end;
                end if;
 
-               --  If any of the index types was an enumeration type with
-               --  a non-standard rep clause, then we indicate that the
-               --  array type is always packed (even if it is not bit packed).
+               --  If any of the index types was an enumeration type with a
+               --  non-standard rep clause, then we indicate that the array
+               --  type is always packed (even if it is not bit packed).
 
                if Non_Standard_Enum then
                   Set_Has_Non_Standard_Rep (Base_Type (E));
@@ -3344,7 +3570,7 @@ package body Freeze is
                  and then Ekind (E) /= E_String_Literal_Subtype
                then
                   Create_Packed_Array_Type (E);
-                  Freeze_And_Append (Packed_Array_Type (E), Loc, Result);
+                  Freeze_And_Append (Packed_Array_Type (E), N, Result);
 
                   --  Size information of packed array type is copied to the
                   --  array type, since this is really the representation. But
@@ -3387,7 +3613,7 @@ package body Freeze is
          --  frozen as well (RM 13.14(15))
 
          elsif Is_Class_Wide_Type (E) then
-            Freeze_And_Append (Root_Type (E), Loc, Result);
+            Freeze_And_Append (Root_Type (E), N, Result);
 
             --  If the base type of the class-wide type is still incomplete,
             --  the class-wide remains unfrozen as well. This is legal when
@@ -3413,11 +3639,7 @@ package body Freeze is
 
                begin
                   Set_Itype (Ref, E);
-                  if No (Result) then
-                     Result := New_List (Ref);
-                  else
-                     Append (Ref, Result);
-                  end if;
+                  Add_To_Result (Ref);
                end;
             end if;
 
@@ -3427,7 +3649,7 @@ package body Freeze is
             if Ekind (E) = E_Class_Wide_Subtype
               and then Present (Equivalent_Type (E))
             then
-               Freeze_And_Append (Equivalent_Type (E), Loc, Result);
+               Freeze_And_Append (Equivalent_Type (E), N, Result);
             end if;
 
          --  For a record (sub)type, freeze all the component types (RM
@@ -3451,13 +3673,13 @@ package body Freeze is
          elsif Is_Concurrent_Type (E) then
             if Present (Corresponding_Record_Type (E)) then
                Freeze_And_Append
-                 (Corresponding_Record_Type (E), Loc, Result);
+                 (Corresponding_Record_Type (E), N, Result);
             end if;
 
             Comp := First_Entity (E);
             while Present (Comp) loop
                if Is_Type (Comp) then
-                  Freeze_And_Append (Comp, Loc, Result);
+                  Freeze_And_Append (Comp, N, Result);
 
                elsif (Ekind (Comp)) /= E_Function then
                   if Is_Itype (Etype (Comp))
@@ -3466,7 +3688,7 @@ package body Freeze is
                      Undelay_Type (Etype (Comp));
                   end if;
 
-                  Freeze_And_Append (Etype (Comp), Loc, Result);
+                  Freeze_And_Append (Etype (Comp), N, Result);
                end if;
 
                Next_Entity (Comp);
@@ -3499,7 +3721,7 @@ package body Freeze is
             --     package Pkg is
             --        type T is tagged private;
             --        type DT is new T with private;
-            --        procedure Prim (X : in out T; Y : in out DT'class);
+            --        procedure Prim (X : in out T; Y : in out DT'Class);
             --     private
             --        type T is tagged null record;
             --        Obj : T;
@@ -3524,7 +3746,6 @@ package body Freeze is
                --  processing is required
 
                if Is_Frozen (Full_View (E)) then
-
                   Set_Has_Delayed_Freeze (E, False);
                   Set_Freeze_Node (E, Empty);
                   Check_Debug_Info_Needed (E);
@@ -3541,10 +3762,10 @@ package body Freeze is
                        and then Present (Underlying_Full_View (Full))
                      then
                         Freeze_And_Append
-                          (Underlying_Full_View (Full), Loc, Result);
+                          (Underlying_Full_View (Full), N, Result);
                      end if;
 
-                     Freeze_And_Append (Full, Loc, Result);
+                     Freeze_And_Append (Full, N, Result);
 
                      if Has_Delayed_Freeze (E) then
                         F_Node := Freeze_Node (Full);
@@ -3615,7 +3836,6 @@ package body Freeze is
 
          elsif Ekind (E) = E_Subprogram_Type then
             Formal := First_Formal (E);
-
             while Present (Formal) loop
                if Ekind (Etype (Formal)) = E_Incomplete_Type
                  and then No (Full_View (Etype (Formal)))
@@ -3623,13 +3843,17 @@ package body Freeze is
                then
                   if Is_Tagged_Type (Etype (Formal)) then
                      null;
-                  else
+
+                  --  AI05-151: Incomplete types are allowed in access to
+                  --  subprogram specifications.
+
+                  elsif Ada_Version < Ada_2012 then
                      Error_Msg_NE
                        ("invalid use of incomplete type&", E, Etype (Formal));
                   end if;
                end if;
 
-               Freeze_And_Append (Etype (Formal), Loc, Result);
+               Freeze_And_Append (Etype (Formal), N, Result);
                Next_Formal (Formal);
             end loop;
 
@@ -3641,7 +3865,7 @@ package body Freeze is
 
          elsif Is_Access_Protected_Subprogram_Type (E) then
             if Present (Equivalent_Type (E)) then
-               Freeze_And_Append (Equivalent_Type (E), Loc, Result);
+               Freeze_And_Append (Equivalent_Type (E), N, Result);
             end if;
          end if;
 
@@ -3663,9 +3887,7 @@ package body Freeze is
             --  these till the freeze-point since we need the small and range
             --  values. We only do these checks for base types
 
-            if Is_Ordinary_Fixed_Point_Type (E)
-              and then E = Base_Type (E)
-            then
+            if Is_Ordinary_Fixed_Point_Type (E) and then Is_Base_Type (E) then
                if Small_Value (E) < Ureal_2_M_80 then
                   Error_Msg_Name_1 := Name_Small;
                   Error_Msg_N
@@ -3704,6 +3926,28 @@ package body Freeze is
 
          elsif Is_Access_Type (E) then
 
+            --  If a pragma Default_Storage_Pool applies, and this type has no
+            --  Storage_Pool or Storage_Size clause (which must have occurred
+            --  before the freezing point), then use the default. This applies
+            --  only to base types.
+
+            if Present (Default_Pool)
+              and then Is_Base_Type (E)
+              and then not Has_Storage_Size_Clause (E)
+              and then No (Associated_Storage_Pool (E))
+            then
+               --  Case of pragma Default_Storage_Pool (null)
+
+               if Nkind (Default_Pool) = N_Null then
+                  Set_No_Pool_Assigned (E);
+
+               --  Case of pragma Default_Storage_Pool (storage_pool_NAME)
+
+               else
+                  Set_Associated_Storage_Pool (E, Entity (Default_Pool));
+               end if;
+            end if;
+
             --  Check restriction for standard storage pool
 
             if No (Associated_Storage_Pool (E)) then
@@ -3714,12 +3958,12 @@ package body Freeze is
             --  error in Ada 2005 if there is no pool (see AI-366).
 
             if Is_Pure_Unit_Access_Type (E)
-              and then (Ada_Version < Ada_05
+              and then (Ada_Version < Ada_2005
                          or else not No_Pool_Assigned (E))
             then
                Error_Msg_N ("named access type not allowed in pure unit", E);
 
-               if Ada_Version >= Ada_05 then
+               if Ada_Version >= Ada_2005 then
                   Error_Msg_N
                     ("\would be legal if Storage_Size of 0 given?", E);
 
@@ -3758,6 +4002,7 @@ package body Freeze is
                declare
                   Prim_List : constant Elist_Id := Primitive_Operations (E);
                   Prim      : Elmt_Id;
+
                begin
                   Prim := First_Elmt (Prim_List);
                   while Present (Prim) loop
@@ -3798,11 +4043,11 @@ package body Freeze is
             end if;
          end if;
 
-         --  Remaining process is to set/verify the representation information,
-         --  in particular the size and alignment values. This processing is
-         --  not required for generic types, since generic types do not play
-         --  any part in code generation, and so the size and alignment values
-         --  for such types are irrelevant.
+         --  Now we set/verify the representation information, in particular
+         --  the size and alignment values. This processing is not required for
+         --  generic types, since generic types do not play any part in code
+         --  generation, and so the size and alignment values for such types
+         --  are irrelevant.
 
          if Is_Generic_Type (E) then
             return Result;
@@ -3813,6 +4058,42 @@ package body Freeze is
             Layout_Type (E);
          end if;
 
+         --  If the type has a Defaut_Value/Default_Component_Value aspect,
+         --  this is where we analye the expression (after the type is frozen,
+         --  since in the case of Default_Value, we are analyzing with the
+         --  type itself, and we treat Default_Component_Value similarly for
+         --  the sake of uniformity.
+
+         if Is_First_Subtype (E) and then Has_Default_Aspect (E) then
+            declare
+               Nam    : Name_Id;
+               Aspect : Node_Id;
+               Exp    : Node_Id;
+               Typ    : Entity_Id;
+
+            begin
+               if Is_Scalar_Type (E) then
+                  Nam := Name_Default_Value;
+                  Typ := E;
+               else
+                  Nam := Name_Default_Component_Value;
+                  Typ := Component_Type (E);
+               end if;
+
+               Aspect := Get_Rep_Item_For_Entity (E, Nam);
+               Exp := Expression (Aspect);
+               Analyze_And_Resolve (Exp, Typ);
+
+               if Etype (Exp) /= Any_Type then
+                  if not Is_Static_Expression (Exp) then
+                     Error_Msg_Name_1 := Nam;
+                     Flag_Non_Static_Expr
+                       ("aspect% requires static expression", Exp);
+                  end if;
+               end if;
+            end;
+         end if;
+
          --  End of freeze processing for type entities
       end if;
 
@@ -3840,12 +4121,7 @@ package body Freeze is
          end if;
 
          Set_Entity (F_Node, E);
-
-         if Result = No_List then
-            Result := New_List (F_Node);
-         else
-            Append (F_Node, Result);
-         end if;
+         Add_To_Result (F_Node);
 
          --  A final pass over record types with discriminants. If the type
          --  has an incomplete declaration, there may be constrained access
@@ -3865,7 +4141,6 @@ package body Freeze is
 
             begin
                Comp := First_Component (E);
-
                while Present (Comp) loop
                   Typ  := Etype (Comp);
 
@@ -3891,7 +4166,7 @@ package body Freeze is
       --  since obviously the first subtype depends on its own base type.
 
       if Is_Type (E) then
-         Freeze_And_Append (First_Subtype (E), Loc, Result);
+         Freeze_And_Append (First_Subtype (E), N, Result);
 
          --  If we just froze a tagged non-class wide record, then freeze the
          --  corresponding class-wide type. This must be done after the tagged
@@ -3902,7 +4177,7 @@ package body Freeze is
            and then not Is_Class_Wide_Type (E)
            and then Present (Class_Wide_Type (E))
          then
-            Freeze_And_Append (Class_Wide_Type (E), Loc, Result);
+            Freeze_And_Append (Class_Wide_Type (E), N, Result);
          end if;
       end if;
 
@@ -3924,6 +4199,8 @@ package body Freeze is
          --  subprogram in main unit, generate descriptor if we are in
          --  Propagate_Exceptions mode.
 
+         --  This is very odd code, it makes a null result, why ???
+
          elsif Propagate_Exceptions
            and then Is_Imported (E)
            and then not Is_Intrinsic_Subprogram (E)
@@ -4324,33 +4601,34 @@ package body Freeze is
             --  is a statement or declaration and we can insert the freeze node
             --  before it.
 
-            when N_Package_Specification |
+            when N_Block_Statement       |
+                 N_Entry_Body            |
                  N_Package_Body          |
-                 N_Subprogram_Body       |
-                 N_Task_Body             |
+                 N_Package_Specification |
                  N_Protected_Body        |
-                 N_Entry_Body            |
-                 N_Block_Statement       => exit;
+                 N_Subprogram_Body       |
+                 N_Task_Body             => exit;
 
             --  The expander is allowed to define types in any statements list,
             --  so any of the following parent nodes also mark a freezing point
             --  if the actual node is in a list of statements or declarations.
 
-            when N_Exception_Handler          |
-                 N_If_Statement               |
-                 N_Elsif_Part                 |
+            when N_Abortable_Part             |
+                 N_Accept_Alternative         |
+                 N_And_Then                   |
                  N_Case_Statement_Alternative |
                  N_Compilation_Unit_Aux       |
-                 N_Selective_Accept           |
-                 N_Accept_Alternative         |
-                 N_Delay_Alternative          |
                  N_Conditional_Entry_Call     |
+                 N_Delay_Alternative          |
+                 N_Elsif_Part                 |
                  N_Entry_Call_Alternative     |
-                 N_Triggering_Alternative     |
-                 N_Abortable_Part             |
-                 N_And_Then                   |
+                 N_Exception_Handler          |
+                 N_Extended_Return_Statement  |
+                 N_Freeze_Entity              |
+                 N_If_Statement               |
                  N_Or_Else                    |
-                 N_Freeze_Entity              =>
+                 N_Selective_Accept           |
+                 N_Triggering_Alternative     =>
 
                exit when Is_List_Member (P);
 
@@ -4408,35 +4686,39 @@ package body Freeze is
         or else Ekind (Current_Scope) = E_Void
       then
          declare
-            Loc          : constant Source_Ptr := Sloc (Current_Scope);
-            Freeze_Nodes : List_Id := No_List;
-            Pos          : Int := Scope_Stack.Last;
+            N            : constant Node_Id    := Current_Scope;
+            Freeze_Nodes : List_Id             := No_List;
+            Pos          : Int                 := Scope_Stack.Last;
 
          begin
             if Present (Desig_Typ) then
-               Freeze_And_Append (Desig_Typ, Loc, Freeze_Nodes);
+               Freeze_And_Append (Desig_Typ, N, Freeze_Nodes);
             end if;
 
             if Present (Typ) then
-               Freeze_And_Append (Typ, Loc, Freeze_Nodes);
+               Freeze_And_Append (Typ, N, Freeze_Nodes);
             end if;
 
             if Present (Nam) then
-               Freeze_And_Append (Nam, Loc, Freeze_Nodes);
+               Freeze_And_Append (Nam, N, Freeze_Nodes);
             end if;
 
             --  The current scope may be that of a constrained component of
             --  an enclosing record declaration, which is above the current
             --  scope in the scope stack.
+            --  If the expression is within a top-level pragma, as for a pre-
+            --  condition on a library-level subprogram, nothing to do.
 
-            if Is_Record_Type (Scope (Current_Scope)) then
+            if not Is_Compilation_Unit (Current_Scope)
+              and then Is_Record_Type (Scope (Current_Scope))
+            then
                Pos := Pos - 1;
             end if;
 
             if Is_Non_Empty_List (Freeze_Nodes) then
                if No (Scope_Stack.Table (Pos).Pending_Freeze_Actions) then
                   Scope_Stack.Table (Pos).Pending_Freeze_Actions :=
-                      Freeze_Nodes;
+                    Freeze_Nodes;
                else
                   Append_List (Freeze_Nodes,
                     Scope_Stack.Table (Pos).Pending_Freeze_Actions);
@@ -4749,11 +5031,7 @@ package body Freeze is
                --  natural boundary of size.
 
                elsif Size_Incl_EP /= Size_Excl_EP
-                 and then
-                    (Size_Excl_EP = 8  or else
-                     Size_Excl_EP = 16 or else
-                     Size_Excl_EP = 32 or else
-                     Size_Excl_EP = 64)
+                 and then Addressable (Size_Excl_EP)
                then
                   Actual_Size := Size_Excl_EP;
                   Actual_Lo   := Loval_Excl_EP;
@@ -4943,7 +5221,7 @@ package body Freeze is
 
    begin
       Set_Has_Delayed_Freeze (T);
-      L := Freeze_Entity (T, Sloc (N));
+      L := Freeze_Entity (T, N);
 
       if Is_Non_Empty_List (L) then
          Insert_Actions (N, L);
@@ -5052,7 +5330,6 @@ package body Freeze is
                   end if;
 
                   F := First_Formal (Designated_Type (Typ));
-
                   while Present (F) loop
                      Ensure_Type_Is_SA (Etype (F));
                      Next_Formal (F);
@@ -5216,13 +5493,13 @@ package body Freeze is
 
               and then Mechanism (E) not in Descriptor_Codes
 
-              --  Check appropriate warning is enabled (should we check for
-              --  Warnings (Off) on specific entities here, probably so???)
+               --  Check appropriate warning is enabled (should we check for
+               --  Warnings (Off) on specific entities here, probably so???)
 
               and then Warn_On_Export_Import
 
-               --  Exclude the VM case, since return of unconstrained arrays
-               --  is properly handled in both the JVM and .NET cases.
+              --  Exclude the VM case, since return of unconstrained arrays
+              --  is properly handled in both the JVM and .NET cases.
 
               and then VM_Target = No_VM
             then
@@ -5336,7 +5613,6 @@ package body Freeze is
 
          begin
             Comp := First_Component (T);
-
             while Present (Comp) loop
                if not Is_Fully_Defined (Etype (Comp)) then
                   return False;
@@ -5487,16 +5763,14 @@ package body Freeze is
 
                    Declarations => New_List (
                      Make_Object_Declaration (Loc,
-                       Defining_Identifier =>
-                         Make_Defining_Identifier (Loc,
-                           New_Internal_Name ('T')),
-                         Object_Definition =>
-                           New_Occurrence_Of (Etype (Formal), Loc),
-                         Expression => New_Copy_Tree (Dcopy))),
+                       Defining_Identifier => Make_Temporary (Loc, 'T'),
+                       Object_Definition   =>
+                         New_Occurrence_Of (Etype (Formal), Loc),
+                       Expression          => New_Copy_Tree (Dcopy))),
 
                    Handled_Statement_Sequence =>
                      Make_Handled_Sequence_Of_Statements (Loc,
-                       Statements => New_List));
+                       Statements => Empty_List));
 
                Set_Scope (Dnam, Scope (E));
                Set_Assignment_OK (First (Declarations (Dbody)));
@@ -5617,15 +5891,16 @@ package body Freeze is
       --  tested for because predefined String types are initialized by inline
       --  code rather than by an init_proc). Note that we do not give the
       --  warning for Initialize_Scalars, since we suppressed initialization
-      --  in this case.
+      --  in this case. Also, do not warn if Suppress_Initialization is set.
 
       if Present (Expr)
         and then not Is_Imported (Ent)
+        and then not Initialization_Suppressed (Typ)
         and then (Has_Non_Null_Base_Init_Proc (Typ)
-                    or else Is_Access_Type (Typ)
-                    or else (Normalize_Scalars
-                              and then (Is_Scalar_Type (Typ)
-                                         or else Is_String_Type (Typ))))
+                   or else Is_Access_Type (Typ)
+                   or else (Normalize_Scalars
+                             and then (Is_Scalar_Type (Typ)
+                                        or else Is_String_Type (Typ))))
       then
          if Nkind (Expr) = N_Attribute_Reference
            and then Is_Entity_Name (Prefix (Expr))
@@ -5688,7 +5963,6 @@ package body Freeze is
 
             begin
                Comp := First_Component (Typ);
-
                while Present (Comp) loop
                   if Nkind (Parent (Comp)) = N_Component_Declaration
                     and then Present (Expression (Parent (Comp)))