[Ada] Attribute Old for capturing old values

Arnaud Charlet charlet@adacore.com
Thu Mar 27 09:06:00 GMT 2008


Tested on i686-linux, committed on trunk

This patch implements a new attribute 'Old. This can be used in a
subprogram to refer to the value of the prefix on entry. So for
example if you have an argument of a record type X called Arg1,
you can refer to Arg1.Field'Old which yields the value of
Arg1.Field on entry. The implementation simply involves generating
an object declaration which captures the value on entry. Any
prefix is allowed except one of a limited type (since limited
types cannot be copied to capture their values).

This test shows the use of 'Old to implement something
approximating postconditions:

with Old_Pkg;
procedure Old is
begin
   Old_Pkg.Incr;
end Old;

package Old_Pkg is
   procedure Incr;
end Old_Pkg;

package body Old_Pkg is
   Count : Natural := 0;

   procedure Incr is
   begin
      Count := Count + 2;
      pragma Assert (Count = Count'Old + 1);
   end Incr;
end Old_Pkg;

Compiled with -gnata, this generates at run time:

raised SYSTEM.ASSERTIONS.ASSERT_FAILURE : old_pkg.adb:7

The second example shows the error on limited types:

     1. procedure limited_old is
     2.    type x is limited record
     3.       y : integer;
     4.    end record;
     5.
     6.    g : x;
     7.
     8.    procedure k (arg : x) is
     9.    begin
    10.       if arg'old = g then
                 |
        >>> attribute "old" cannot apply to limited objects

    11.          null;
    12.       end if;
    13.    end;
    14.
    15. begin
    16.    null;
    17. end;

2008-03-26  Javier Miranda  <miranda@adacore.com>
	    Robert Dewar  <dewar@adacore.com>

	* exp_attr.adb (N_Pragma): Chars field removed.
	(Expand_N_Attribute_Reference): If the designated type associated with
	attribute 'Unrestricted_Access is a subprogram entity then replace it
	by an E_Subprogram_Type itype.
	Implement attribute Old

	* sem_attr.ads (Attribute_Class_Array): Move to snames.ads

	* sem_attr.adb (Build_Access_Subprogram_Itype): Add documentation.
	Replace call to
	New_Internal_Entity by call to Create_Itype to centralize calls
	building itypes, ad propagate the convention of the designated
	subprogram. In addition, disable the machinery cleaning constant
	indications from all entities in current scope when 'Unrestricted_Access
	corresponds with a node initializing a dispatch table slot.
	(Analyze_Attribute): Parameterless attributes returning a string or a
	type will not be called with improper arguments, so we can remove junk
	code that was dealing with this case.
	Implement attribute Old

	* snames.ads, snames.h, snames.adb: Add entries for attribute Old
	Add entry for pragma Optimize_Alignment
	New standard names Sync and Synchronize

-------------- next part --------------
Index: exp_attr.adb
===================================================================
--- exp_attr.adb	(revision 133430)
+++ exp_attr.adb	(working copy)
@@ -6,7 +6,7 @@
 --                                                                          --
 --                                 B o d y                                  --
 --                                                                          --
---          Copyright (C) 1992-2007, Free Software Foundation, Inc.         --
+--          Copyright (C) 1992-2008, 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- --
@@ -49,6 +49,7 @@ with Restrict; use Restrict;
 with Rident;   use Rident;
 with Rtsfind;  use Rtsfind;
 with Sem;      use Sem;
+with Sem_Ch6;  use Sem_Ch6;
 with Sem_Ch7;  use Sem_Ch7;
 with Sem_Ch8;  use Sem_Ch8;
 with Sem_Eval; use Sem_Eval;
@@ -611,6 +612,121 @@ package body Exp_Attr is
             Ref_Object : constant Node_Id := Get_Referenced_Object (Pref);
 
          begin
+            --  In order to improve the text of error messages, the designated
+            --  type of access-to-subprogram itypes is set by the semantics as
+            --  the associated subprogram entity (see sem_attr). Now we replace
+            --  such node with the proper E_Subprogram_Type itype.
+
+            if Id = Attribute_Unrestricted_Access
+              and then Is_Subprogram (Directly_Designated_Type (Typ))
+            then
+               --  The following assertion ensures that this special management
+               --  is done only for "Address!(Prim'Unrestricted_Access)" nodes.
+               --  At this stage other cases in which the designated type is
+               --  still a subprogram (instead of an E_Subprogram_Type) are
+               --  wrong because the semantics must have overriden the type of
+               --  the node with the type imposed by the context.
+
+               pragma Assert (Nkind (Parent (N)) = N_Unchecked_Type_Conversion
+                 and then Etype (Parent (N)) = RTE (RE_Address));
+
+               declare
+                  Subp : constant Entity_Id := Directly_Designated_Type (Typ);
+
+                  Extra      : Entity_Id := Empty;
+                  New_Formal : Entity_Id;
+                  Old_Formal : Entity_Id := First_Formal (Subp);
+                  Subp_Typ   : Entity_Id;
+
+               begin
+                  Subp_Typ := Create_Itype (E_Subprogram_Type, N);
+                  Set_Etype (Subp_Typ, Etype (Subp));
+                  Set_Returns_By_Ref (Subp_Typ, Returns_By_Ref (Subp));
+
+                  if Present (Old_Formal) then
+                     New_Formal := New_Copy (Old_Formal);
+                     Set_First_Entity (Subp_Typ, New_Formal);
+
+                     loop
+                        Set_Scope (New_Formal, Subp_Typ);
+
+                        --  Handle itypes
+
+                        if Is_Itype (Etype (New_Formal)) then
+                           Extra := New_Copy (Etype (New_Formal));
+
+                           if Ekind (Extra) = E_Record_Subtype
+                             or else Ekind (Extra) = E_Class_Wide_Subtype
+                           then
+                              Set_Cloned_Subtype (Extra,
+                                Etype (New_Formal));
+                           end if;
+
+                           Set_Etype (New_Formal, Extra);
+                           Set_Scope (Etype (New_Formal), Subp_Typ);
+                        end if;
+
+                        Extra := New_Formal;
+                        Next_Formal (Old_Formal);
+                        exit when No (Old_Formal);
+
+                        Set_Next_Entity (New_Formal,
+                          New_Copy (Old_Formal));
+                        Next_Entity (New_Formal);
+                     end loop;
+
+                     Set_Next_Entity (New_Formal, Empty);
+                     Set_Last_Entity (Subp_Typ, Extra);
+                  end if;
+
+                  --  Now that the explicit formals have been duplicated,
+                  --  any extra formals needed by the subprogram must be
+                  --  created.
+
+                  if Present (Extra) then
+                     Set_Extra_Formal (Extra, Empty);
+                  end if;
+
+                  Create_Extra_Formals (Subp_Typ);
+                  Set_Directly_Designated_Type (Typ, Subp_Typ);
+
+                  --  Complete decoration of access-to-subprogram itype to
+                  --  indicate to the backend that this itype corresponds to
+                  --  a statically allocated dispatch table.
+
+                  --  ??? more comments on structure here, three level parent
+                  --  references are worrisome!
+
+                  if Nkind (Ref_Object) in N_Has_Entity
+                    and then Is_Dispatching_Operation (Entity (Ref_Object))
+                    and then Present (Parent (Parent (N)))
+                    and then Nkind (Parent (Parent (N))) = N_Aggregate
+                    and then Present (Parent (Parent (Parent (N))))
+                  then
+                     declare
+                        P    : constant Node_Id :=
+                                 Parent (Parent (Parent (N)));
+                        Prim : constant Entity_Id := Entity (Ref_Object);
+
+                     begin
+                        Set_Is_Static_Dispatch_Table_Entity (Typ,
+                           (Is_Predefined_Dispatching_Operation (Prim)
+                              and then Nkind (P) = N_Object_Declaration
+                              and then Is_Static_Dispatch_Table_Entity
+                                         (Defining_Identifier (P)))
+                          or else
+                           (not Is_Predefined_Dispatching_Operation (Prim)
+                              and then Nkind (P) = N_Aggregate
+                              and then Present (Parent (P))
+                              and then Nkind (Parent (P))
+                                         = N_Object_Declaration
+                              and then Is_Static_Dispatch_Table_Entity
+                                         (Defining_Identifier (Parent (P)))));
+                     end;
+                  end if;
+               end;
+            end if;
+
             if Is_Access_Protected_Subprogram_Type (Btyp) then
                Expand_Access_To_Protected_Op (N, Pref, Typ);
 
@@ -1208,18 +1324,20 @@ package body Exp_Attr is
          --  Protected case
 
          if Is_Protected_Type (Conctype) then
-            if Abort_Allowed
-              or else Restriction_Active (No_Entry_Queue) = False
-              or else Number_Entries (Conctype) > 1
-            then
-               Name :=
-                 New_Reference_To
-                   (RTE (RE_Protected_Entry_Caller), Loc);
-            else
-               Name :=
-                 New_Reference_To
-                   (RTE (RE_Protected_Single_Entry_Caller), Loc);
-            end if;
+            case Corresponding_Runtime_Package (Conctype) is
+               when System_Tasking_Protected_Objects_Entries =>
+                  Name :=
+                    New_Reference_To
+                      (RTE (RE_Protected_Entry_Caller), Loc);
+
+               when System_Tasking_Protected_Objects_Single_Entry =>
+                  Name :=
+                    New_Reference_To
+                      (RTE (RE_Protected_Single_Entry_Caller), Loc);
+
+               when others =>
+                  raise Program_Error;
+            end case;
 
             Rewrite (N,
               Unchecked_Convert_To (Id_Kind,
@@ -1488,31 +1606,35 @@ package body Exp_Attr is
 
          if Is_Protected_Type (Conctyp) then
 
-            if Abort_Allowed
-              or else Restriction_Active (No_Entry_Queue) = False
-              or else Number_Entries (Conctyp) > 1
-            then
-               Name := New_Reference_To (RTE (RE_Protected_Count), Loc);
-
-               Call :=
-                 Make_Function_Call (Loc,
-                   Name => Name,
-                   Parameter_Associations => New_List (
-                     New_Reference_To (
-                       Object_Ref (
-                         Corresponding_Body (Parent (Conctyp))), Loc),
-                     Entry_Index_Expression (
-                       Loc, Entity (Entnam), Index, Scope (Entity (Entnam)))));
-            else
-               Name := New_Reference_To (RTE (RE_Protected_Count_Entry), Loc);
+            case Corresponding_Runtime_Package (Conctyp) is
+               when System_Tasking_Protected_Objects_Entries =>
+                  Name := New_Reference_To (RTE (RE_Protected_Count), Loc);
+
+                  Call :=
+                    Make_Function_Call (Loc,
+                      Name => Name,
+                      Parameter_Associations => New_List (
+                        New_Reference_To (
+                          Object_Ref (
+                            Corresponding_Body (Parent (Conctyp))), Loc),
+                        Entry_Index_Expression (Loc,
+                          Entity (Entnam), Index, Scope (Entity (Entnam)))));
+
+               when System_Tasking_Protected_Objects_Single_Entry =>
+                  Name := New_Reference_To
+                           (RTE (RE_Protected_Count_Entry), Loc);
+
+                  Call :=
+                    Make_Function_Call (Loc,
+                      Name => Name,
+                      Parameter_Associations => New_List (
+                        New_Reference_To (
+                          Object_Ref (
+                            Corresponding_Body (Parent (Conctyp))), Loc)));
+               when others =>
+                  raise Program_Error;
 
-               Call := Make_Function_Call (Loc,
-                   Name => Name,
-                   Parameter_Associations => New_List (
-                     New_Reference_To (
-                       Object_Ref (
-                         Corresponding_Body (Parent (Conctyp))), Loc)));
-            end if;
+            end case;
 
          --  Task case
 
@@ -2726,6 +2848,41 @@ package body Exp_Attr is
 
       --  The processing for Object_Size shares the processing for Size
 
+      ---------
+      -- Old --
+      ---------
+
+      when Attribute_Old => Old : declare
+         Tnn     : constant Entity_Id :=
+                     Make_Defining_Identifier (Loc,
+                       Chars => New_Internal_Name ('T'));
+         Subp    : Node_Id;
+         Asn_Stm : Node_Id;
+
+      begin
+         Subp := N;
+         loop
+            Subp := Parent (Subp);
+            exit when Nkind (Subp) = N_Subprogram_Body;
+         end loop;
+
+         Asn_Stm :=
+           Make_Object_Declaration (Loc,
+             Defining_Identifier => Tnn,
+             Constant_Present    => True,
+             Object_Definition   => New_Occurrence_Of (Etype (N), Loc),
+             Expression          => Pref);
+
+         if Is_Empty_List (Declarations (Subp)) then
+            Set_Declarations (Subp, New_List (Asn_Stm));
+            Analyze (Asn_Stm);
+         else
+            Insert_Action (First (Declarations (Subp)), Asn_Stm);
+         end if;
+
+         Rewrite (N, New_Occurrence_Of (Tnn, Loc));
+      end Old;
+
       ------------
       -- Output --
       ------------
@@ -5177,8 +5334,9 @@ package body Exp_Attr is
 
       N := First_Rep_Item (Implementation_Base_Type (T));
       while Present (N) loop
-         if Nkind (N) = N_Pragma and then Chars (N) = Name_Stream_Convert then
-
+         if Nkind (N) = N_Pragma
+           and then Pragma_Name (N) = Name_Stream_Convert
+         then
             --  For tagged types this pragma is not inherited, so we
             --  must verify that it is defined for the given type and
             --  not an ancestor.
Index: sem_attr.adb
===================================================================
--- sem_attr.adb	(revision 133430)
+++ sem_attr.adb	(working copy)
@@ -35,6 +35,7 @@ with Exp_Dist; use Exp_Dist;
 with Exp_Util; use Exp_Util;
 with Expander; use Expander;
 with Freeze;   use Freeze;
+with Itypes;   use Itypes;
 with Lib;      use Lib;
 with Lib.Xref; use Lib.Xref;
 with Nlists;   use Nlists;
@@ -447,18 +448,41 @@ package body Sem_Attr is
             --  subprogram itself as the designated type. Type-checking in
             --  this case compares the signatures of the designated types.
 
+            --  Note: This fragment of the tree is temporarily malformed
+            --  because the correct tree requires an E_Subprogram_Type entity
+            --  as the designated type. In most cases this designated type is
+            --  later overriden by the semantics with the type imposed by the
+            --  context during the resolution phase. In the specific case of
+            --  the expression Address!(Prim'Unrestricted_Access), used to
+            --  initialize slots of dispatch tables, this work will be done by
+            --  the expander (see Exp_Aggr).
+
+            --  The reason to temporarily add this kind of node to the tree
+            --  instead of a proper E_Subprogram_Type itype, is the following:
+            --  in case of errors found in the source file we report better
+            --  error messages. For example, instead of generating the
+            --  following error:
+
+            --      "expected access to subprogram with profile
+            --       defined at line X"
+
+            --  we currently generate:
+
+            --      "expected access to function Z defined at line X"
+
             Set_Etype (N, Any_Type);
 
             if not Is_Overloaded (P) then
                Check_Local_Access (Entity (P));
 
                if not Is_Intrinsic_Subprogram (Entity (P)) then
-                  Acc_Type :=
-                    New_Internal_Entity
-                      (Get_Kind (Entity (P)), Current_Scope, Loc, 'A');
+                  Acc_Type := Create_Itype (Get_Kind (Entity (P)), N);
+                  Set_Is_Public (Acc_Type, False);
                   Set_Etype (Acc_Type, Acc_Type);
+                  Set_Convention (Acc_Type, Convention (Entity (P)));
                   Set_Directly_Designated_Type (Acc_Type, Entity (P));
                   Set_Etype (N, Acc_Type);
+                  Freeze_Before (N, Acc_Type);
                end if;
 
             else
@@ -467,12 +491,13 @@ package body Sem_Attr is
                   Check_Local_Access (It.Nam);
 
                   if not Is_Intrinsic_Subprogram (It.Nam) then
-                     Acc_Type :=
-                       New_Internal_Entity
-                         (Get_Kind (It.Nam), Current_Scope, Loc, 'A');
+                     Acc_Type := Create_Itype (Get_Kind (It.Nam), N);
+                     Set_Is_Public (Acc_Type, False);
                      Set_Etype (Acc_Type, Acc_Type);
+                     Set_Convention (Acc_Type, Convention (It.Nam));
                      Set_Directly_Designated_Type (Acc_Type, It.Nam);
                      Add_One_Interp (N, Acc_Type, Acc_Type);
+                     Freeze_Before (N, Acc_Type);
                   end if;
 
                   Get_Next_Interp (Index, It);
@@ -502,9 +527,7 @@ package body Sem_Attr is
                (Nkind (Par) = N_Component_Association
                  or else Nkind (Par) in N_Subexpr)
             loop
-               if Nkind (Par) = N_Aggregate
-                 or else Nkind (Par) = N_Extension_Aggregate
-               then
+               if Nkind_In (Par, N_Aggregate, N_Extension_Aggregate) then
                   if Etype (Par) = Typ then
                      Set_Has_Self_Reference (Par);
                      return True;
@@ -552,7 +575,23 @@ package body Sem_Attr is
             --  could modify local variables to be passed out of scope
 
             if Aname = Name_Unrestricted_Access then
-               Kill_Current_Values;
+
+               --  Do not kill values on nodes initializing dispatch tables
+               --  slots. The construct Address!(Prim'Unrestricted_Access)
+               --  is currently generated by the expander only for this
+               --  purpose. Done to keep the quality of warnings currently
+               --  generated by the compiler (otherwise any declaration of
+               --  a tagged type cleans constant indications from its scope).
+
+               if Nkind (Parent (N)) = N_Unchecked_Type_Conversion
+                 and then Etype (Parent (N)) = RTE (RE_Address)
+                 and then Is_Dispatching_Operation
+                            (Directly_Designated_Type (Etype (N)))
+               then
+                  null;
+               else
+                  Kill_Current_Values;
+               end if;
             end if;
 
             return;
@@ -626,10 +665,9 @@ package body Sem_Attr is
 
                   if not In_Default_Expression
                     and then not Has_Completion (Scop)
-                    and then
-                      Nkind (Parent (N)) /= N_Discriminant_Association
-                    and then
-                      Nkind (Parent (N)) /= N_Index_Or_Discriminant_Constraint
+                    and then not
+                      Nkind_In (Parent (N), N_Discriminant_Association,
+                                            N_Index_Or_Discriminant_Constraint)
                   then
                      Error_Msg_N
                        ("current instance attribute must appear alone", N);
@@ -726,8 +764,8 @@ package body Sem_Attr is
                   Kill_Current_Values (Ent);
                   exit;
 
-               elsif Nkind (PP) = N_Selected_Component
-                 or else Nkind (PP) = N_Indexed_Component
+               elsif Nkind_In (PP, N_Selected_Component,
+                                   N_Indexed_Component)
                then
                   PP := Prefix (PP);
 
@@ -1414,8 +1452,8 @@ package body Sem_Attr is
             null;
 
          elsif Is_List_Member (N)
-           and then Nkind (Parent (N)) /= N_Procedure_Call_Statement
-           and then Nkind (Parent (N)) /= N_Aggregate
+           and then not Nkind_In (Parent (N), N_Procedure_Call_Statement,
+                                              N_Aggregate)
          then
             null;
 
@@ -2145,9 +2183,7 @@ package body Sem_Attr is
          --  or of a variable of the enclosing task type.
 
          else
-            if Nkind (Pref) = N_Identifier
-              or else Nkind (Pref) = N_Expanded_Name
-            then
+            if Nkind_In (Pref, N_Identifier, N_Expanded_Name) then
                Ent := Entity (Pref);
 
                if not OK_Entry (Ent)
@@ -2297,9 +2333,7 @@ package body Sem_Attr is
       begin
          Check_E0;
 
-         if Nkind (P) = N_Identifier
-           or else Nkind (P) = N_Expanded_Name
-         then
+         if Nkind_In (P, N_Identifier, N_Expanded_Name) then
             Ent := Entity (P);
 
             if not Is_Entry (Ent) then
@@ -2500,9 +2534,7 @@ package body Sem_Attr is
       begin
          Check_E0;
 
-         if Nkind (P) = N_Identifier
-           or else Nkind (P) = N_Expanded_Name
-         then
+         if Nkind_In (P, N_Identifier, N_Expanded_Name) then
             Ent := Entity (P);
 
             if Ekind (Ent) /= E_Entry then
@@ -2623,7 +2655,6 @@ package body Sem_Attr is
       when Attribute_Default_Bit_Order => Default_Bit_Order :
       begin
          Check_Standard_Prefix;
-         Check_E0;
 
          if Bytes_Big_Endian then
             Rewrite (N,
@@ -2733,7 +2764,6 @@ package body Sem_Attr is
 
          if Nkind (P) /= N_Identifier then
             Error_Msg_N ("identifier expected (check name)", P);
-
          elsif Get_Check_Id (Chars (P)) = No_Check_Id then
             Error_Msg_N ("& is not a recognized check name", P);
          end if;
@@ -2802,7 +2832,6 @@ package body Sem_Attr is
       ---------------
 
       when Attribute_Fast_Math =>
-         Check_E0;
          Check_Standard_Prefix;
 
          if Opt.Fast_Math then
@@ -3320,9 +3349,8 @@ package body Sem_Attr is
 
          --  Case of attribute used as actual for subprogram (positional)
 
-         elsif (Nkind (Parnt) = N_Procedure_Call_Statement
-                 or else
-                Nkind (Parnt) = N_Function_Call)
+         elsif Nkind_In (Parnt, N_Procedure_Call_Statement,
+                                N_Function_Call)
             and then Is_Entity_Name (Name (Parnt))
          then
             Must_Be_Imported (Entity (Name (Parnt)));
@@ -3330,9 +3358,8 @@ package body Sem_Attr is
          --  Case of attribute used as actual for subprogram (named)
 
          elsif Nkind (Parnt) = N_Parameter_Association
-           and then (Nkind (GParnt) = N_Procedure_Call_Statement
-                       or else
-                     Nkind (GParnt) = N_Function_Call)
+           and then Nkind_In (GParnt, N_Procedure_Call_Statement,
+                                      N_Function_Call)
            and then Is_Entity_Name (Name (GParnt))
          then
             Must_Be_Imported (Entity (Name (GParnt)));
@@ -3343,7 +3370,6 @@ package body Sem_Attr is
             Bad_Null_Parameter
               ("Null_Parameter must be actual or default parameter");
          end if;
-
       end Null_Parameter;
 
       -----------------
@@ -3356,6 +3382,22 @@ package body Sem_Attr is
          Check_Not_Incomplete_Type;
          Set_Etype (N, Universal_Integer);
 
+      ---------
+      -- Old --
+      ---------
+
+      when Attribute_Old =>
+         Check_E0;
+         Set_Etype (N, P_Type);
+
+         if not Is_Subprogram (Current_Scope) then
+            Error_Attr ("attribute % can only appear within subprogram", N);
+         end if;
+
+         if Is_Limited_Type (P_Type) then
+            Error_Attr ("attribute % cannot apply to limited objects", P);
+         end if;
+
       ------------
       -- Output --
       ------------
@@ -3370,7 +3412,8 @@ package body Sem_Attr is
       -- Partition_ID --
       ------------------
 
-      when Attribute_Partition_ID =>
+      when Attribute_Partition_ID => Partition_Id :
+      begin
          Check_E0;
 
          if P_Type /= Any_Type then
@@ -3378,9 +3421,8 @@ package body Sem_Attr is
                Error_Attr_P
                  ("prefix of % attribute must be library-level entity");
 
-            --  The defining entity of prefix should not be declared inside
-            --  a Pure unit. RM E.1(8).
-            --  The Is_Pure flag has been set during declaration.
+            --  The defining entity of prefix should not be declared inside a
+            --  Pure unit. RM E.1(8). Is_Pure was set during declaration.
 
             elsif Is_Entity_Name (P)
               and then Is_Pure (Entity (P))
@@ -3391,6 +3433,7 @@ package body Sem_Attr is
          end if;
 
          Set_Etype (N, Universal_Integer);
+      end Partition_Id;
 
       -------------------------
       -- Passed_By_Reference --
@@ -3522,6 +3565,7 @@ package body Sem_Attr is
       ------------------
 
       when Attribute_Range_Length =>
+         Check_E0;
          Check_Discrete_Type;
          Set_Etype (N, Universal_Integer);
 
@@ -3654,7 +3698,8 @@ package body Sem_Attr is
       -- Size --
       ----------
 
-      when Attribute_Size | Attribute_VADS_Size =>
+      when Attribute_Size | Attribute_VADS_Size => Size :
+      begin
          Check_E0;
 
          --  If prefix is parameterless function call, rewrite and resolve
@@ -3693,6 +3738,7 @@ package body Sem_Attr is
 
          Check_Not_Incomplete_Type;
          Set_Etype (N, Universal_Integer);
+      end Size;
 
       -----------
       -- Small --
@@ -3707,10 +3753,11 @@ package body Sem_Attr is
       -- Storage_Pool --
       ------------------
 
-      when Attribute_Storage_Pool =>
-         if Is_Access_Type (P_Type) then
-            Check_E0;
+      when Attribute_Storage_Pool => Storage_Pool :
+      begin
+         Check_E0;
 
+         if Is_Access_Type (P_Type) then
             if Ekind (P_Type) = E_Access_Subprogram_Type then
                Error_Attr_P
                  ("cannot use % attribute for access-to-subprogram type");
@@ -3735,14 +3782,17 @@ package body Sem_Attr is
          else
             Error_Attr_P ("prefix of % attribute must be access type");
          end if;
+      end Storage_Pool;
 
       ------------------
       -- Storage_Size --
       ------------------
 
-      when Attribute_Storage_Size =>
+      when Attribute_Storage_Size => Storage_Size :
+      begin
+         Check_E0;
+
          if Is_Task_Type (P_Type) then
-            Check_E0;
             Set_Etype (N, Universal_Integer);
 
          elsif Is_Access_Type (P_Type) then
@@ -3754,7 +3804,6 @@ package body Sem_Attr is
             if Is_Entity_Name (P)
               and then Is_Type (Entity (P))
             then
-               Check_E0;
                Check_Type;
                Set_Etype (N, Universal_Integer);
 
@@ -3768,7 +3817,6 @@ package body Sem_Attr is
             --  of an access value designating a task.
 
             else
-               Check_E0;
                Check_Task_Prefix;
                Set_Etype (N, Universal_Integer);
             end if;
@@ -3776,6 +3824,7 @@ package body Sem_Attr is
          else
             Error_Attr_P ("prefix of % attribute must be access or task type");
          end if;
+      end Storage_Size;
 
       ------------------
       -- Storage_Unit --
@@ -3845,7 +3894,8 @@ package body Sem_Attr is
       -- Tag --
       ---------
 
-      when Attribute_Tag =>
+      when Attribute_Tag => Tag :
+      begin
          Check_E0;
          Check_Dereference;
 
@@ -3875,6 +3925,7 @@ package body Sem_Attr is
          --  Set appropriate type
 
          Set_Etype (N, RTE (RE_Tag));
+      end Tag;
 
       -----------------
       -- Target_Name --
@@ -3886,7 +3937,6 @@ package body Sem_Attr is
 
       begin
          Check_Standard_Prefix;
-         Check_E0;
 
          TL := TN'Last;
 
@@ -4022,9 +4072,7 @@ package body Sem_Attr is
                   Negative := False;
                end if;
 
-               if Nkind (Expr) /= N_Integer_Literal
-                 and then Nkind (Expr) /= N_Real_Literal
-               then
+               if not Nkind_In (Expr, N_Integer_Literal, N_Real_Literal) then
                   Error_Attr
                     ("named number for % attribute must be simple literal", N);
                end if;
@@ -4987,12 +5035,11 @@ package body Sem_Attr is
       then
          P_Type := P_Entity;
 
-      --  We can fold 'Size applied to a type if the size is known
-      --  (as happens for a size from an attribute definition clause).
-      --  At this stage, this can happen only for types (e.g. record
-      --  types) for which the size is always non-static. We exclude
-      --  generic types from consideration (since they have bogus
-      --  sizes set within templates).
+      --  We can fold 'Size applied to a type if the size is known (as happens
+      --  for a size from an attribute definition clause). At this stage, this
+      --  can happen only for types (e.g. record types) for which the size is
+      --  always non-static. We exclude generic types from consideration (since
+      --  they have bogus sizes set within templates).
 
       elsif Id = Attribute_Size
         and then Is_Type (P_Entity)
@@ -6924,6 +6971,7 @@ package body Sem_Attr is
            Attribute_Input                    |
            Attribute_Last_Bit                 |
            Attribute_Maximum_Alignment        |
+           Attribute_Old                      |
            Attribute_Output                   |
            Attribute_Partition_ID             |
            Attribute_Pool_Address             |
@@ -6961,10 +7009,10 @@ package body Sem_Attr is
       --  An exception is the GNAT attribute Constrained_Array which is
       --  defined to be a static attribute in all cases.
 
-      if Nkind (N) = N_Integer_Literal
-        or else Nkind (N) = N_Real_Literal
-        or else Nkind (N) = N_Character_Literal
-        or else Nkind (N) = N_String_Literal
+      if Nkind_In (N, N_Integer_Literal,
+                      N_Real_Literal,
+                      N_Character_Literal,
+                      N_String_Literal)
         or else (Is_Entity_Name (N)
                   and then Ekind (Entity (N)) = E_Enumeration_Literal)
       then
@@ -7060,9 +7108,8 @@ package body Sem_Attr is
 
             if Is_Record_Type (Current_Scope)
               and then
-                (Nkind (Parent (N)) = N_Discriminant_Association
-                   or else
-                 Nkind (Parent (N)) = N_Index_Or_Discriminant_Constraint)
+                Nkind_In (Parent (N), N_Discriminant_Association,
+                                      N_Index_Or_Discriminant_Constraint)
             then
                Indic := Parent (Parent (N));
                while Present (Indic)
@@ -7122,7 +7169,8 @@ package body Sem_Attr is
             | Attribute_Unchecked_Access
             | Attribute_Unrestricted_Access =>
 
-         Access_Attribute : begin
+         Access_Attribute :
+         begin
             if Is_Variable (P) then
                Note_Possible_Modification (P);
             end if;
Index: snames.ads
===================================================================
--- snames.ads	(revision 133430)
+++ snames.ads	(working copy)
@@ -371,37 +371,38 @@ package Snames is
    Name_No_Run_Time                    : constant Name_Id := N + 145; -- GNAT
    Name_No_Strict_Aliasing             : constant Name_Id := N + 146; -- GNAT
    Name_Normalize_Scalars              : constant Name_Id := N + 147;
-   Name_Polling                        : constant Name_Id := N + 148; -- GNAT
-   Name_Persistent_BSS                 : constant Name_Id := N + 149; -- GNAT
-   Name_Priority_Specific_Dispatching  : constant Name_Id := N + 150; -- Ada 05
-   Name_Profile                        : constant Name_Id := N + 151; -- Ada 05
-   Name_Profile_Warnings               : constant Name_Id := N + 152; -- GNAT
-   Name_Propagate_Exceptions           : constant Name_Id := N + 153; -- GNAT
-   Name_Queuing_Policy                 : constant Name_Id := N + 154;
-   Name_Ravenscar                      : constant Name_Id := N + 155; -- GNAT
-   Name_Restricted_Run_Time            : constant Name_Id := N + 156; -- GNAT
-   Name_Restrictions                   : constant Name_Id := N + 157;
-   Name_Restriction_Warnings           : constant Name_Id := N + 158; -- GNAT
-   Name_Reviewable                     : constant Name_Id := N + 159;
-   Name_Source_File_Name               : constant Name_Id := N + 160; -- GNAT
-   Name_Source_File_Name_Project       : constant Name_Id := N + 161; -- GNAT
-   Name_Style_Checks                   : constant Name_Id := N + 162; -- GNAT
-   Name_Suppress                       : constant Name_Id := N + 163;
-   Name_Suppress_Exception_Locations   : constant Name_Id := N + 164; -- GNAT
-   Name_Task_Dispatching_Policy        : constant Name_Id := N + 165;
-   Name_Universal_Data                 : constant Name_Id := N + 166; -- AAMP
-   Name_Unsuppress                     : constant Name_Id := N + 167; -- GNAT
-   Name_Use_VADS_Size                  : constant Name_Id := N + 168; -- GNAT
-   Name_Validity_Checks                : constant Name_Id := N + 169; -- GNAT
-   Name_Warnings                       : constant Name_Id := N + 170; -- GNAT
-   Name_Wide_Character_Encoding        : constant Name_Id := N + 171; -- GNAT
-   Last_Configuration_Pragma_Name      : constant Name_Id := N + 171;
+   Name_Optimize_Alignment             : constant Name_Id := N + 148; -- GNAT
+   Name_Polling                        : constant Name_Id := N + 149; -- GNAT
+   Name_Persistent_BSS                 : constant Name_Id := N + 150; -- GNAT
+   Name_Priority_Specific_Dispatching  : constant Name_Id := N + 151; -- Ada 05
+   Name_Profile                        : constant Name_Id := N + 152; -- Ada 05
+   Name_Profile_Warnings               : constant Name_Id := N + 153; -- GNAT
+   Name_Propagate_Exceptions           : constant Name_Id := N + 154; -- GNAT
+   Name_Queuing_Policy                 : constant Name_Id := N + 155;
+   Name_Ravenscar                      : constant Name_Id := N + 156; -- GNAT
+   Name_Restricted_Run_Time            : constant Name_Id := N + 157; -- GNAT
+   Name_Restrictions                   : constant Name_Id := N + 158;
+   Name_Restriction_Warnings           : constant Name_Id := N + 159; -- GNAT
+   Name_Reviewable                     : constant Name_Id := N + 160;
+   Name_Source_File_Name               : constant Name_Id := N + 161; -- GNAT
+   Name_Source_File_Name_Project       : constant Name_Id := N + 162; -- GNAT
+   Name_Style_Checks                   : constant Name_Id := N + 163; -- GNAT
+   Name_Suppress                       : constant Name_Id := N + 164;
+   Name_Suppress_Exception_Locations   : constant Name_Id := N + 165; -- GNAT
+   Name_Task_Dispatching_Policy        : constant Name_Id := N + 166;
+   Name_Universal_Data                 : constant Name_Id := N + 167; -- AAMP
+   Name_Unsuppress                     : constant Name_Id := N + 168; -- GNAT
+   Name_Use_VADS_Size                  : constant Name_Id := N + 169; -- GNAT
+   Name_Validity_Checks                : constant Name_Id := N + 170; -- GNAT
+   Name_Warnings                       : constant Name_Id := N + 171; -- GNAT
+   Name_Wide_Character_Encoding        : constant Name_Id := N + 172; -- GNAT
+   Last_Configuration_Pragma_Name      : constant Name_Id := N + 172;
 
    --  Remaining pragma names
 
-   Name_Abort_Defer                    : constant Name_Id := N + 172; -- GNAT
-   Name_All_Calls_Remote               : constant Name_Id := N + 173;
-   Name_Annotate                       : constant Name_Id := N + 174; -- GNAT
+   Name_Abort_Defer                    : constant Name_Id := N + 173; -- GNAT
+   Name_All_Calls_Remote               : constant Name_Id := N + 174;
+   Name_Annotate                       : constant Name_Id := N + 175; -- GNAT
 
    --  Note: AST_Entry is not in this list because its name matches   -- VMS
    --  the name of the corresponding attribute. However, it is
@@ -409,74 +410,74 @@ package Snames is
    --  functions Get_Pragma_Id and Is_Pragma_Id correctly recognize
    --  and process Name_AST_Entry.
 
-   Name_Assert                         : constant Name_Id := N + 175; -- Ada 05
-   Name_Asynchronous                   : constant Name_Id := N + 176;
-   Name_Atomic                         : constant Name_Id := N + 177;
-   Name_Atomic_Components              : constant Name_Id := N + 178;
-   Name_Attach_Handler                 : constant Name_Id := N + 179;
-   Name_CIL_Constructor                : constant Name_Id := N + 180; -- GNAT
-   Name_Comment                        : constant Name_Id := N + 181; -- GNAT
-   Name_Common_Object                  : constant Name_Id := N + 182; -- GNAT
-   Name_Complete_Representation        : constant Name_Id := N + 183; -- GNAT
-   Name_Complex_Representation         : constant Name_Id := N + 184; -- GNAT
-   Name_Controlled                     : constant Name_Id := N + 185;
-   Name_Convention                     : constant Name_Id := N + 186;
-   Name_CPP_Class                      : constant Name_Id := N + 187; -- GNAT
-   Name_CPP_Constructor                : constant Name_Id := N + 188; -- GNAT
-   Name_CPP_Virtual                    : constant Name_Id := N + 189; -- GNAT
-   Name_CPP_Vtable                     : constant Name_Id := N + 190; -- GNAT
-   Name_Debug                          : constant Name_Id := N + 191; -- GNAT
-   Name_Elaborate                      : constant Name_Id := N + 192; -- Ada 83
-   Name_Elaborate_All                  : constant Name_Id := N + 193;
-   Name_Elaborate_Body                 : constant Name_Id := N + 194;
-   Name_Export                         : constant Name_Id := N + 195;
-   Name_Export_Exception               : constant Name_Id := N + 196; -- VMS
-   Name_Export_Function                : constant Name_Id := N + 197; -- GNAT
-   Name_Export_Object                  : constant Name_Id := N + 198; -- GNAT
-   Name_Export_Procedure               : constant Name_Id := N + 199; -- GNAT
-   Name_Export_Value                   : constant Name_Id := N + 200; -- GNAT
-   Name_Export_Valued_Procedure        : constant Name_Id := N + 201; -- GNAT
-   Name_External                       : constant Name_Id := N + 202; -- GNAT
-   Name_Finalize_Storage_Only          : constant Name_Id := N + 203; -- GNAT
-   Name_Ident                          : constant Name_Id := N + 204; -- VMS
-   Name_Implemented_By_Entry           : constant Name_Id := N + 205; -- Ada 05
-   Name_Import                         : constant Name_Id := N + 206;
-   Name_Import_Exception               : constant Name_Id := N + 207; -- VMS
-   Name_Import_Function                : constant Name_Id := N + 208; -- GNAT
-   Name_Import_Object                  : constant Name_Id := N + 209; -- GNAT
-   Name_Import_Procedure               : constant Name_Id := N + 210; -- GNAT
-   Name_Import_Valued_Procedure        : constant Name_Id := N + 211; -- GNAT
-   Name_Inline                         : constant Name_Id := N + 212;
-   Name_Inline_Always                  : constant Name_Id := N + 213; -- GNAT
-   Name_Inline_Generic                 : constant Name_Id := N + 214; -- GNAT
-   Name_Inspection_Point               : constant Name_Id := N + 215;
-   Name_Interface_Name                 : constant Name_Id := N + 216; -- GNAT
-   Name_Interrupt_Handler              : constant Name_Id := N + 217;
-   Name_Interrupt_Priority             : constant Name_Id := N + 218;
-   Name_Java_Constructor               : constant Name_Id := N + 219; -- GNAT
-   Name_Java_Interface                 : constant Name_Id := N + 220; -- GNAT
-   Name_Keep_Names                     : constant Name_Id := N + 221; -- GNAT
-   Name_Link_With                      : constant Name_Id := N + 222; -- GNAT
-   Name_Linker_Alias                   : constant Name_Id := N + 223; -- GNAT
-   Name_Linker_Constructor             : constant Name_Id := N + 224; -- GNAT
-   Name_Linker_Destructor              : constant Name_Id := N + 225; -- GNAT
-   Name_Linker_Options                 : constant Name_Id := N + 226;
-   Name_Linker_Section                 : constant Name_Id := N + 227; -- GNAT
-   Name_List                           : constant Name_Id := N + 228;
-   Name_Machine_Attribute              : constant Name_Id := N + 229; -- GNAT
-   Name_Main                           : constant Name_Id := N + 230; -- GNAT
-   Name_Main_Storage                   : constant Name_Id := N + 231; -- GNAT
-   Name_Memory_Size                    : constant Name_Id := N + 232; -- Ada 83
-   Name_No_Body                        : constant Name_Id := N + 233; -- GNAT
-   Name_No_Return                      : constant Name_Id := N + 234; -- GNAT
-   Name_Obsolescent                    : constant Name_Id := N + 235; -- GNAT
-   Name_Optimize                       : constant Name_Id := N + 236;
-   Name_Pack                           : constant Name_Id := N + 237;
-   Name_Page                           : constant Name_Id := N + 238;
-   Name_Passive                        : constant Name_Id := N + 239; -- GNAT
-   Name_Preelaborable_Initialization   : constant Name_Id := N + 240; -- Ada 05
-   Name_Preelaborate                   : constant Name_Id := N + 241;
-   Name_Preelaborate_05                : constant Name_Id := N + 242; -- GNAT
+   Name_Assert                         : constant Name_Id := N + 176; -- Ada 05
+   Name_Asynchronous                   : constant Name_Id := N + 177;
+   Name_Atomic                         : constant Name_Id := N + 178;
+   Name_Atomic_Components              : constant Name_Id := N + 179;
+   Name_Attach_Handler                 : constant Name_Id := N + 180;
+   Name_CIL_Constructor                : constant Name_Id := N + 181; -- GNAT
+   Name_Comment                        : constant Name_Id := N + 182; -- GNAT
+   Name_Common_Object                  : constant Name_Id := N + 183; -- GNAT
+   Name_Complete_Representation        : constant Name_Id := N + 184; -- GNAT
+   Name_Complex_Representation         : constant Name_Id := N + 185; -- GNAT
+   Name_Controlled                     : constant Name_Id := N + 186;
+   Name_Convention                     : constant Name_Id := N + 187;
+   Name_CPP_Class                      : constant Name_Id := N + 188; -- GNAT
+   Name_CPP_Constructor                : constant Name_Id := N + 189; -- GNAT
+   Name_CPP_Virtual                    : constant Name_Id := N + 190; -- GNAT
+   Name_CPP_Vtable                     : constant Name_Id := N + 191; -- GNAT
+   Name_Debug                          : constant Name_Id := N + 192; -- GNAT
+   Name_Elaborate                      : constant Name_Id := N + 193; -- Ada 83
+   Name_Elaborate_All                  : constant Name_Id := N + 194;
+   Name_Elaborate_Body                 : constant Name_Id := N + 195;
+   Name_Export                         : constant Name_Id := N + 196;
+   Name_Export_Exception               : constant Name_Id := N + 197; -- VMS
+   Name_Export_Function                : constant Name_Id := N + 198; -- GNAT
+   Name_Export_Object                  : constant Name_Id := N + 199; -- GNAT
+   Name_Export_Procedure               : constant Name_Id := N + 200; -- GNAT
+   Name_Export_Value                   : constant Name_Id := N + 201; -- GNAT
+   Name_Export_Valued_Procedure        : constant Name_Id := N + 202; -- GNAT
+   Name_External                       : constant Name_Id := N + 203; -- GNAT
+   Name_Finalize_Storage_Only          : constant Name_Id := N + 204; -- GNAT
+   Name_Ident                          : constant Name_Id := N + 205; -- VMS
+   Name_Implemented_By_Entry           : constant Name_Id := N + 206; -- Ada 05
+   Name_Import                         : constant Name_Id := N + 207;
+   Name_Import_Exception               : constant Name_Id := N + 208; -- VMS
+   Name_Import_Function                : constant Name_Id := N + 209; -- GNAT
+   Name_Import_Object                  : constant Name_Id := N + 210; -- GNAT
+   Name_Import_Procedure               : constant Name_Id := N + 211; -- GNAT
+   Name_Import_Valued_Procedure        : constant Name_Id := N + 212; -- GNAT
+   Name_Inline                         : constant Name_Id := N + 213;
+   Name_Inline_Always                  : constant Name_Id := N + 214; -- GNAT
+   Name_Inline_Generic                 : constant Name_Id := N + 215; -- GNAT
+   Name_Inspection_Point               : constant Name_Id := N + 216;
+   Name_Interface_Name                 : constant Name_Id := N + 217; -- GNAT
+   Name_Interrupt_Handler              : constant Name_Id := N + 218;
+   Name_Interrupt_Priority             : constant Name_Id := N + 219;
+   Name_Java_Constructor               : constant Name_Id := N + 220; -- GNAT
+   Name_Java_Interface                 : constant Name_Id := N + 221; -- GNAT
+   Name_Keep_Names                     : constant Name_Id := N + 222; -- GNAT
+   Name_Link_With                      : constant Name_Id := N + 223; -- GNAT
+   Name_Linker_Alias                   : constant Name_Id := N + 224; -- GNAT
+   Name_Linker_Constructor             : constant Name_Id := N + 225; -- GNAT
+   Name_Linker_Destructor              : constant Name_Id := N + 226; -- GNAT
+   Name_Linker_Options                 : constant Name_Id := N + 227;
+   Name_Linker_Section                 : constant Name_Id := N + 228; -- GNAT
+   Name_List                           : constant Name_Id := N + 229;
+   Name_Machine_Attribute              : constant Name_Id := N + 230; -- GNAT
+   Name_Main                           : constant Name_Id := N + 231; -- GNAT
+   Name_Main_Storage                   : constant Name_Id := N + 232; -- GNAT
+   Name_Memory_Size                    : constant Name_Id := N + 233; -- Ada 83
+   Name_No_Body                        : constant Name_Id := N + 234; -- GNAT
+   Name_No_Return                      : constant Name_Id := N + 235; -- GNAT
+   Name_Obsolescent                    : constant Name_Id := N + 236; -- GNAT
+   Name_Optimize                       : constant Name_Id := N + 237;
+   Name_Pack                           : constant Name_Id := N + 238;
+   Name_Page                           : constant Name_Id := N + 239;
+   Name_Passive                        : constant Name_Id := N + 240; -- GNAT
+   Name_Preelaborable_Initialization   : constant Name_Id := N + 241; -- Ada 05
+   Name_Preelaborate                   : constant Name_Id := N + 242;
+   Name_Preelaborate_05                : constant Name_Id := N + 243; -- GNAT
 
    --  Note: Priority is not in this list because its name matches
    --  the name of the corresponding attribute. However, it is
@@ -484,15 +485,15 @@ package Snames is
    --  functions Get_Pragma_Id and Is_Pragma_Id correctly recognize
    --  and process Priority. Priority is a standard Ada 95 pragma.
 
-   Name_Psect_Object                   : constant Name_Id := N + 243; -- VMS
-   Name_Pure                           : constant Name_Id := N + 244;
-   Name_Pure_05                        : constant Name_Id := N + 245; -- GNAT
-   Name_Pure_Function                  : constant Name_Id := N + 246; -- GNAT
-   Name_Remote_Call_Interface          : constant Name_Id := N + 247;
-   Name_Remote_Types                   : constant Name_Id := N + 248;
-   Name_Share_Generic                  : constant Name_Id := N + 249; -- GNAT
-   Name_Shared                         : constant Name_Id := N + 250; -- Ada 83
-   Name_Shared_Passive                 : constant Name_Id := N + 251;
+   Name_Psect_Object                   : constant Name_Id := N + 244; -- VMS
+   Name_Pure                           : constant Name_Id := N + 245;
+   Name_Pure_05                        : constant Name_Id := N + 246; -- GNAT
+   Name_Pure_Function                  : constant Name_Id := N + 247; -- GNAT
+   Name_Remote_Call_Interface          : constant Name_Id := N + 248;
+   Name_Remote_Types                   : constant Name_Id := N + 249;
+   Name_Share_Generic                  : constant Name_Id := N + 250; -- GNAT
+   Name_Shared                         : constant Name_Id := N + 251; -- Ada 83
+   Name_Shared_Passive                 : constant Name_Id := N + 252;
 
    --  Note: Storage_Size is not in this list because its name
    --  matches the name of the corresponding attribute. However,
@@ -503,30 +504,30 @@ package Snames is
    --  Note: Storage_Unit is also omitted from the list because
    --  of a clash with an attribute name, and is treated similarly.
 
-   Name_Source_Reference               : constant Name_Id := N + 252; -- GNAT
-   Name_Static_Elaboration_Desired     : constant Name_Id := N + 253; -- GNAT
-   Name_Stream_Convert                 : constant Name_Id := N + 254; -- GNAT
-   Name_Subtitle                       : constant Name_Id := N + 255; -- GNAT
-   Name_Suppress_All                   : constant Name_Id := N + 256; -- GNAT
-   Name_Suppress_Debug_Info            : constant Name_Id := N + 257; -- GNAT
-   Name_Suppress_Initialization        : constant Name_Id := N + 258; -- GNAT
-   Name_System_Name                    : constant Name_Id := N + 259; -- Ada 83
-   Name_Task_Info                      : constant Name_Id := N + 260; -- GNAT
-   Name_Task_Name                      : constant Name_Id := N + 261; -- GNAT
-   Name_Task_Storage                   : constant Name_Id := N + 262; -- VMS
-   Name_Time_Slice                     : constant Name_Id := N + 263; -- GNAT
-   Name_Title                          : constant Name_Id := N + 264; -- GNAT
-   Name_Unchecked_Union                : constant Name_Id := N + 265; -- GNAT
-   Name_Unimplemented_Unit             : constant Name_Id := N + 266; -- GNAT
-   Name_Universal_Aliasing             : constant Name_Id := N + 267; -- GNAT
-   Name_Unmodified                     : constant Name_Id := N + 268; -- GNAT
-   Name_Unreferenced                   : constant Name_Id := N + 269; -- GNAT
-   Name_Unreferenced_Objects           : constant Name_Id := N + 270; -- GNAT
-   Name_Unreserve_All_Interrupts       : constant Name_Id := N + 271; -- GNAT
-   Name_Volatile                       : constant Name_Id := N + 272;
-   Name_Volatile_Components            : constant Name_Id := N + 273;
-   Name_Weak_External                  : constant Name_Id := N + 274; -- GNAT
-   Last_Pragma_Name                    : constant Name_Id := N + 274;
+   Name_Source_Reference               : constant Name_Id := N + 253; -- GNAT
+   Name_Static_Elaboration_Desired     : constant Name_Id := N + 254; -- GNAT
+   Name_Stream_Convert                 : constant Name_Id := N + 255; -- GNAT
+   Name_Subtitle                       : constant Name_Id := N + 256; -- GNAT
+   Name_Suppress_All                   : constant Name_Id := N + 257; -- GNAT
+   Name_Suppress_Debug_Info            : constant Name_Id := N + 258; -- GNAT
+   Name_Suppress_Initialization        : constant Name_Id := N + 259; -- GNAT
+   Name_System_Name                    : constant Name_Id := N + 260; -- Ada 83
+   Name_Task_Info                      : constant Name_Id := N + 261; -- GNAT
+   Name_Task_Name                      : constant Name_Id := N + 262; -- GNAT
+   Name_Task_Storage                   : constant Name_Id := N + 263; -- VMS
+   Name_Time_Slice                     : constant Name_Id := N + 264; -- GNAT
+   Name_Title                          : constant Name_Id := N + 265; -- GNAT
+   Name_Unchecked_Union                : constant Name_Id := N + 266; -- GNAT
+   Name_Unimplemented_Unit             : constant Name_Id := N + 267; -- GNAT
+   Name_Universal_Aliasing             : constant Name_Id := N + 268; -- GNAT
+   Name_Unmodified                     : constant Name_Id := N + 269; -- GNAT
+   Name_Unreferenced                   : constant Name_Id := N + 270; -- GNAT
+   Name_Unreferenced_Objects           : constant Name_Id := N + 271; -- GNAT
+   Name_Unreserve_All_Interrupts       : constant Name_Id := N + 272; -- GNAT
+   Name_Volatile                       : constant Name_Id := N + 273;
+   Name_Volatile_Components            : constant Name_Id := N + 274;
+   Name_Weak_External                  : constant Name_Id := N + 275; -- GNAT
+   Last_Pragma_Name                    : constant Name_Id := N + 275;
 
    --  Language convention names for pragma Convention/Export/Import/Interface
    --  Note that Name_C is not included in this list, since it was already
@@ -537,119 +538,119 @@ package Snames is
    --  Entry and Protected, this is because these conventions cannot be
    --  specified by a pragma.
 
-   First_Convention_Name               : constant Name_Id := N + 275;
-   Name_Ada                            : constant Name_Id := N + 275;
-   Name_Assembler                      : constant Name_Id := N + 276;
-   Name_CIL                            : constant Name_Id := N + 277;
-   Name_COBOL                          : constant Name_Id := N + 278;
-   Name_CPP                            : constant Name_Id := N + 279;
-   Name_Fortran                        : constant Name_Id := N + 280;
-   Name_Intrinsic                      : constant Name_Id := N + 281;
-   Name_Java                           : constant Name_Id := N + 282;
-   Name_Stdcall                        : constant Name_Id := N + 283;
-   Name_Stubbed                        : constant Name_Id := N + 284;
-   Last_Convention_Name                : constant Name_Id := N + 284;
+   First_Convention_Name               : constant Name_Id := N + 276;
+   Name_Ada                            : constant Name_Id := N + 276;
+   Name_Assembler                      : constant Name_Id := N + 277;
+   Name_CIL                            : constant Name_Id := N + 278;
+   Name_COBOL                          : constant Name_Id := N + 279;
+   Name_CPP                            : constant Name_Id := N + 280;
+   Name_Fortran                        : constant Name_Id := N + 281;
+   Name_Intrinsic                      : constant Name_Id := N + 282;
+   Name_Java                           : constant Name_Id := N + 283;
+   Name_Stdcall                        : constant Name_Id := N + 284;
+   Name_Stubbed                        : constant Name_Id := N + 285;
+   Last_Convention_Name                : constant Name_Id := N + 285;
 
    --  The following names are preset as synonyms for Assembler
 
-   Name_Asm                            : constant Name_Id := N + 285;
-   Name_Assembly                       : constant Name_Id := N + 286;
+   Name_Asm                            : constant Name_Id := N + 286;
+   Name_Assembly                       : constant Name_Id := N + 287;
 
    --  The following names are preset as synonyms for C
 
-   Name_Default                        : constant Name_Id := N + 287;
+   Name_Default                        : constant Name_Id := N + 288;
    --  Name_Exernal (previously defined as pragma)
 
    --  The following names are preset as synonyms for CPP
 
-   Name_C_Plus_Plus                    : constant Name_Id := N + 288;
+   Name_C_Plus_Plus                    : constant Name_Id := N + 289;
 
    --  The following names are present as synonyms for Stdcall
 
-   Name_DLL                            : constant Name_Id := N + 289;
-   Name_Win32                          : constant Name_Id := N + 290;
+   Name_DLL                            : constant Name_Id := N + 290;
+   Name_Win32                          : constant Name_Id := N + 291;
 
    --  Other special names used in processing pragmas
 
-   Name_As_Is                          : constant Name_Id := N + 291;
-   Name_Attribute_Name                 : constant Name_Id := N + 292;
-   Name_Body_File_Name                 : constant Name_Id := N + 293;
-   Name_Boolean_Entry_Barriers         : constant Name_Id := N + 294;
-   Name_Check                          : constant Name_Id := N + 295;
-   Name_Casing                         : constant Name_Id := N + 296;
-   Name_Code                           : constant Name_Id := N + 297;
-   Name_Component                      : constant Name_Id := N + 298;
-   Name_Component_Size_4               : constant Name_Id := N + 299;
-   Name_Copy                           : constant Name_Id := N + 300;
-   Name_D_Float                        : constant Name_Id := N + 301;
-   Name_Descriptor                     : constant Name_Id := N + 302;
-   Name_Dot_Replacement                : constant Name_Id := N + 303;
-   Name_Dynamic                        : constant Name_Id := N + 304;
-   Name_Entity                         : constant Name_Id := N + 305;
-   Name_Entry_Count                    : constant Name_Id := N + 306;
-   Name_External_Name                  : constant Name_Id := N + 307;
-   Name_First_Optional_Parameter       : constant Name_Id := N + 308;
-   Name_Form                           : constant Name_Id := N + 309;
-   Name_G_Float                        : constant Name_Id := N + 310;
-   Name_Gcc                            : constant Name_Id := N + 311;
-   Name_Gnat                           : constant Name_Id := N + 312;
-   Name_GPL                            : constant Name_Id := N + 313;
-   Name_IEEE_Float                     : constant Name_Id := N + 314;
-   Name_Ignore                         : constant Name_Id := N + 315;
-   Name_Info                           : constant Name_Id := N + 316;
-   Name_Internal                       : constant Name_Id := N + 317;
-   Name_Link_Name                      : constant Name_Id := N + 318;
-   Name_Lowercase                      : constant Name_Id := N + 319;
-   Name_Max_Entry_Queue_Depth          : constant Name_Id := N + 320;
-   Name_Max_Entry_Queue_Length         : constant Name_Id := N + 321;
-   Name_Max_Size                       : constant Name_Id := N + 322;
-   Name_Mechanism                      : constant Name_Id := N + 323;
-   Name_Message                        : constant Name_Id := N + 324;
-   Name_Mixedcase                      : constant Name_Id := N + 325;
-   Name_Modified_GPL                   : constant Name_Id := N + 326;
-   Name_Name                           : constant Name_Id := N + 327;
-   Name_NCA                            : constant Name_Id := N + 328;
-   Name_No                             : constant Name_Id := N + 329;
-   Name_No_Dependence                  : constant Name_Id := N + 330;
-   Name_No_Dynamic_Attachment          : constant Name_Id := N + 331;
-   Name_No_Dynamic_Interrupts          : constant Name_Id := N + 332;
-   Name_No_Requeue                     : constant Name_Id := N + 333;
-   Name_No_Requeue_Statements          : constant Name_Id := N + 334;
-   Name_No_Task_Attributes             : constant Name_Id := N + 335;
-   Name_No_Task_Attributes_Package     : constant Name_Id := N + 336;
-   Name_On                             : constant Name_Id := N + 337;
-   Name_Parameter_Types                : constant Name_Id := N + 338;
-   Name_Reference                      : constant Name_Id := N + 339;
-   Name_Restricted                     : constant Name_Id := N + 340;
-   Name_Result_Mechanism               : constant Name_Id := N + 341;
-   Name_Result_Type                    : constant Name_Id := N + 342;
-   Name_Runtime                        : constant Name_Id := N + 343;
-   Name_SB                             : constant Name_Id := N + 344;
-   Name_Secondary_Stack_Size           : constant Name_Id := N + 345;
-   Name_Section                        : constant Name_Id := N + 346;
-   Name_Semaphore                      : constant Name_Id := N + 347;
-   Name_Simple_Barriers                : constant Name_Id := N + 348;
-   Name_Spec_File_Name                 : constant Name_Id := N + 349;
-   Name_State                          : constant Name_Id := N + 350;
-   Name_Static                         : constant Name_Id := N + 351;
-   Name_Stack_Size                     : constant Name_Id := N + 352;
-   Name_Subunit_File_Name              : constant Name_Id := N + 353;
-   Name_Task_Stack_Size_Default        : constant Name_Id := N + 354;
-   Name_Task_Type                      : constant Name_Id := N + 355;
-   Name_Time_Slicing_Enabled           : constant Name_Id := N + 356;
-   Name_Top_Guard                      : constant Name_Id := N + 357;
-   Name_UBA                            : constant Name_Id := N + 358;
-   Name_UBS                            : constant Name_Id := N + 359;
-   Name_UBSB                           : constant Name_Id := N + 360;
-   Name_Unit_Name                      : constant Name_Id := N + 361;
-   Name_Unknown                        : constant Name_Id := N + 362;
-   Name_Unrestricted                   : constant Name_Id := N + 363;
-   Name_Uppercase                      : constant Name_Id := N + 364;
-   Name_User                           : constant Name_Id := N + 365;
-   Name_VAX_Float                      : constant Name_Id := N + 366;
-   Name_VMS                            : constant Name_Id := N + 367;
-   Name_Vtable_Ptr                     : constant Name_Id := N + 368;
-   Name_Working_Storage                : constant Name_Id := N + 369;
+   Name_As_Is                          : constant Name_Id := N + 292;
+   Name_Attribute_Name                 : constant Name_Id := N + 293;
+   Name_Body_File_Name                 : constant Name_Id := N + 294;
+   Name_Boolean_Entry_Barriers         : constant Name_Id := N + 295;
+   Name_Check                          : constant Name_Id := N + 296;
+   Name_Casing                         : constant Name_Id := N + 297;
+   Name_Code                           : constant Name_Id := N + 298;
+   Name_Component                      : constant Name_Id := N + 299;
+   Name_Component_Size_4               : constant Name_Id := N + 300;
+   Name_Copy                           : constant Name_Id := N + 301;
+   Name_D_Float                        : constant Name_Id := N + 302;
+   Name_Descriptor                     : constant Name_Id := N + 303;
+   Name_Dot_Replacement                : constant Name_Id := N + 304;
+   Name_Dynamic                        : constant Name_Id := N + 305;
+   Name_Entity                         : constant Name_Id := N + 306;
+   Name_Entry_Count                    : constant Name_Id := N + 307;
+   Name_External_Name                  : constant Name_Id := N + 308;
+   Name_First_Optional_Parameter       : constant Name_Id := N + 309;
+   Name_Form                           : constant Name_Id := N + 310;
+   Name_G_Float                        : constant Name_Id := N + 311;
+   Name_Gcc                            : constant Name_Id := N + 312;
+   Name_Gnat                           : constant Name_Id := N + 313;
+   Name_GPL                            : constant Name_Id := N + 314;
+   Name_IEEE_Float                     : constant Name_Id := N + 315;
+   Name_Ignore                         : constant Name_Id := N + 316;
+   Name_Info                           : constant Name_Id := N + 317;
+   Name_Internal                       : constant Name_Id := N + 318;
+   Name_Link_Name                      : constant Name_Id := N + 319;
+   Name_Lowercase                      : constant Name_Id := N + 320;
+   Name_Max_Entry_Queue_Depth          : constant Name_Id := N + 321;
+   Name_Max_Entry_Queue_Length         : constant Name_Id := N + 322;
+   Name_Max_Size                       : constant Name_Id := N + 323;
+   Name_Mechanism                      : constant Name_Id := N + 324;
+   Name_Message                        : constant Name_Id := N + 325;
+   Name_Mixedcase                      : constant Name_Id := N + 326;
+   Name_Modified_GPL                   : constant Name_Id := N + 327;
+   Name_Name                           : constant Name_Id := N + 328;
+   Name_NCA                            : constant Name_Id := N + 329;
+   Name_No                             : constant Name_Id := N + 330;
+   Name_No_Dependence                  : constant Name_Id := N + 331;
+   Name_No_Dynamic_Attachment          : constant Name_Id := N + 332;
+   Name_No_Dynamic_Interrupts          : constant Name_Id := N + 333;
+   Name_No_Requeue                     : constant Name_Id := N + 334;
+   Name_No_Requeue_Statements          : constant Name_Id := N + 335;
+   Name_No_Task_Attributes             : constant Name_Id := N + 336;
+   Name_No_Task_Attributes_Package     : constant Name_Id := N + 337;
+   Name_On                             : constant Name_Id := N + 338;
+   Name_Parameter_Types                : constant Name_Id := N + 339;
+   Name_Reference                      : constant Name_Id := N + 340;
+   Name_Restricted                     : constant Name_Id := N + 341;
+   Name_Result_Mechanism               : constant Name_Id := N + 342;
+   Name_Result_Type                    : constant Name_Id := N + 343;
+   Name_Runtime                        : constant Name_Id := N + 344;
+   Name_SB                             : constant Name_Id := N + 345;
+   Name_Secondary_Stack_Size           : constant Name_Id := N + 346;
+   Name_Section                        : constant Name_Id := N + 347;
+   Name_Semaphore                      : constant Name_Id := N + 348;
+   Name_Simple_Barriers                : constant Name_Id := N + 349;
+   Name_Spec_File_Name                 : constant Name_Id := N + 350;
+   Name_State                          : constant Name_Id := N + 351;
+   Name_Static                         : constant Name_Id := N + 352;
+   Name_Stack_Size                     : constant Name_Id := N + 353;
+   Name_Subunit_File_Name              : constant Name_Id := N + 354;
+   Name_Task_Stack_Size_Default        : constant Name_Id := N + 355;
+   Name_Task_Type                      : constant Name_Id := N + 356;
+   Name_Time_Slicing_Enabled           : constant Name_Id := N + 357;
+   Name_Top_Guard                      : constant Name_Id := N + 358;
+   Name_UBA                            : constant Name_Id := N + 359;
+   Name_UBS                            : constant Name_Id := N + 360;
+   Name_UBSB                           : constant Name_Id := N + 361;
+   Name_Unit_Name                      : constant Name_Id := N + 362;
+   Name_Unknown                        : constant Name_Id := N + 363;
+   Name_Unrestricted                   : constant Name_Id := N + 364;
+   Name_Uppercase                      : constant Name_Id := N + 365;
+   Name_User                           : constant Name_Id := N + 366;
+   Name_VAX_Float                      : constant Name_Id := N + 367;
+   Name_VMS                            : constant Name_Id := N + 368;
+   Name_Vtable_Ptr                     : constant Name_Id := N + 369;
+   Name_Working_Storage                : constant Name_Id := N + 370;
 
    --  Names of recognized attributes. The entries with the comment "Ada 83"
    --  are attributes that are defined in Ada 83, but not in Ada 95. These
@@ -663,170 +664,171 @@ package Snames is
    --  The entries marked VMS are recognized only in OpenVMS implementations
    --  of GNAT, and are treated as illegal in all other contexts.
 
-   First_Attribute_Name                : constant Name_Id := N + 370;
-   Name_Abort_Signal                   : constant Name_Id := N + 370; -- GNAT
-   Name_Access                         : constant Name_Id := N + 371;
-   Name_Address                        : constant Name_Id := N + 372;
-   Name_Address_Size                   : constant Name_Id := N + 373; -- GNAT
-   Name_Aft                            : constant Name_Id := N + 374;
-   Name_Alignment                      : constant Name_Id := N + 375;
-   Name_Asm_Input                      : constant Name_Id := N + 376; -- GNAT
-   Name_Asm_Output                     : constant Name_Id := N + 377; -- GNAT
-   Name_AST_Entry                      : constant Name_Id := N + 378; -- VMS
-   Name_Bit                            : constant Name_Id := N + 379; -- GNAT
-   Name_Bit_Order                      : constant Name_Id := N + 380;
-   Name_Bit_Position                   : constant Name_Id := N + 381; -- GNAT
-   Name_Body_Version                   : constant Name_Id := N + 382;
-   Name_Callable                       : constant Name_Id := N + 383;
-   Name_Caller                         : constant Name_Id := N + 384;
-   Name_Code_Address                   : constant Name_Id := N + 385; -- GNAT
-   Name_Component_Size                 : constant Name_Id := N + 386;
-   Name_Compose                        : constant Name_Id := N + 387;
-   Name_Constrained                    : constant Name_Id := N + 388;
-   Name_Count                          : constant Name_Id := N + 389;
-   Name_Default_Bit_Order              : constant Name_Id := N + 390; -- GNAT
-   Name_Definite                       : constant Name_Id := N + 391;
-   Name_Delta                          : constant Name_Id := N + 392;
-   Name_Denorm                         : constant Name_Id := N + 393;
-   Name_Digits                         : constant Name_Id := N + 394;
-   Name_Elaborated                     : constant Name_Id := N + 395; -- GNAT
-   Name_Emax                           : constant Name_Id := N + 396; -- Ada 83
-   Name_Enabled                        : constant Name_Id := N + 397; -- GNAT
-   Name_Enum_Rep                       : constant Name_Id := N + 398; -- GNAT
-   Name_Epsilon                        : constant Name_Id := N + 399; -- Ada 83
-   Name_Exponent                       : constant Name_Id := N + 400;
-   Name_External_Tag                   : constant Name_Id := N + 401;
-   Name_Fast_Math                      : constant Name_Id := N + 402; -- GNAT
-   Name_First                          : constant Name_Id := N + 403;
-   Name_First_Bit                      : constant Name_Id := N + 404;
-   Name_Fixed_Value                    : constant Name_Id := N + 405; -- GNAT
-   Name_Fore                           : constant Name_Id := N + 406;
-   Name_Has_Access_Values              : constant Name_Id := N + 407; -- GNAT
-   Name_Has_Discriminants              : constant Name_Id := N + 408; -- GNAT
-   Name_Identity                       : constant Name_Id := N + 409;
-   Name_Img                            : constant Name_Id := N + 410; -- GNAT
-   Name_Integer_Value                  : constant Name_Id := N + 411; -- GNAT
-   Name_Large                          : constant Name_Id := N + 412; -- Ada 83
-   Name_Last                           : constant Name_Id := N + 413;
-   Name_Last_Bit                       : constant Name_Id := N + 414;
-   Name_Leading_Part                   : constant Name_Id := N + 415;
-   Name_Length                         : constant Name_Id := N + 416;
-   Name_Machine_Emax                   : constant Name_Id := N + 417;
-   Name_Machine_Emin                   : constant Name_Id := N + 418;
-   Name_Machine_Mantissa               : constant Name_Id := N + 419;
-   Name_Machine_Overflows              : constant Name_Id := N + 420;
-   Name_Machine_Radix                  : constant Name_Id := N + 421;
-   Name_Machine_Rounding               : constant Name_Id := N + 422; -- Ada 05
-   Name_Machine_Rounds                 : constant Name_Id := N + 423;
-   Name_Machine_Size                   : constant Name_Id := N + 424; -- GNAT
-   Name_Mantissa                       : constant Name_Id := N + 425; -- Ada 83
-   Name_Max_Size_In_Storage_Elements   : constant Name_Id := N + 426;
-   Name_Maximum_Alignment              : constant Name_Id := N + 427; -- GNAT
-   Name_Mechanism_Code                 : constant Name_Id := N + 428; -- GNAT
-   Name_Mod                            : constant Name_Id := N + 429; -- Ada 05
-   Name_Model_Emin                     : constant Name_Id := N + 430;
-   Name_Model_Epsilon                  : constant Name_Id := N + 431;
-   Name_Model_Mantissa                 : constant Name_Id := N + 432;
-   Name_Model_Small                    : constant Name_Id := N + 433;
-   Name_Modulus                        : constant Name_Id := N + 434;
-   Name_Null_Parameter                 : constant Name_Id := N + 435; -- GNAT
-   Name_Object_Size                    : constant Name_Id := N + 436; -- GNAT
-   Name_Partition_ID                   : constant Name_Id := N + 437;
-   Name_Passed_By_Reference            : constant Name_Id := N + 438; -- GNAT
-   Name_Pool_Address                   : constant Name_Id := N + 439;
-   Name_Pos                            : constant Name_Id := N + 440;
-   Name_Position                       : constant Name_Id := N + 441;
-   Name_Priority                       : constant Name_Id := N + 442; -- Ada 05
-   Name_Range                          : constant Name_Id := N + 443;
-   Name_Range_Length                   : constant Name_Id := N + 444; -- GNAT
-   Name_Round                          : constant Name_Id := N + 445;
-   Name_Safe_Emax                      : constant Name_Id := N + 446; -- Ada 83
-   Name_Safe_First                     : constant Name_Id := N + 447;
-   Name_Safe_Large                     : constant Name_Id := N + 448; -- Ada 83
-   Name_Safe_Last                      : constant Name_Id := N + 449;
-   Name_Safe_Small                     : constant Name_Id := N + 450; -- Ada 83
-   Name_Scale                          : constant Name_Id := N + 451;
-   Name_Scaling                        : constant Name_Id := N + 452;
-   Name_Signed_Zeros                   : constant Name_Id := N + 453;
-   Name_Size                           : constant Name_Id := N + 454;
-   Name_Small                          : constant Name_Id := N + 455;
-   Name_Storage_Size                   : constant Name_Id := N + 456;
-   Name_Storage_Unit                   : constant Name_Id := N + 457; -- GNAT
-   Name_Stream_Size                    : constant Name_Id := N + 458; -- Ada 05
-   Name_Tag                            : constant Name_Id := N + 459;
-   Name_Target_Name                    : constant Name_Id := N + 460; -- GNAT
-   Name_Terminated                     : constant Name_Id := N + 461;
-   Name_To_Address                     : constant Name_Id := N + 462; -- GNAT
-   Name_Type_Class                     : constant Name_Id := N + 463; -- GNAT
-   Name_UET_Address                    : constant Name_Id := N + 464; -- GNAT
-   Name_Unbiased_Rounding              : constant Name_Id := N + 465;
-   Name_Unchecked_Access               : constant Name_Id := N + 466;
-   Name_Unconstrained_Array            : constant Name_Id := N + 467;
-   Name_Universal_Literal_String       : constant Name_Id := N + 468; -- GNAT
-   Name_Unrestricted_Access            : constant Name_Id := N + 469; -- GNAT
-   Name_VADS_Size                      : constant Name_Id := N + 470; -- GNAT
-   Name_Val                            : constant Name_Id := N + 471;
-   Name_Valid                          : constant Name_Id := N + 472;
-   Name_Value_Size                     : constant Name_Id := N + 473; -- GNAT
-   Name_Version                        : constant Name_Id := N + 474;
-   Name_Wchar_T_Size                   : constant Name_Id := N + 475; -- GNAT
-   Name_Wide_Wide_Width                : constant Name_Id := N + 476; -- Ada 05
-   Name_Wide_Width                     : constant Name_Id := N + 477;
-   Name_Width                          : constant Name_Id := N + 478;
-   Name_Word_Size                      : constant Name_Id := N + 479; -- GNAT
+   First_Attribute_Name                : constant Name_Id := N + 371;
+   Name_Abort_Signal                   : constant Name_Id := N + 371; -- GNAT
+   Name_Access                         : constant Name_Id := N + 372;
+   Name_Address                        : constant Name_Id := N + 373;
+   Name_Address_Size                   : constant Name_Id := N + 374; -- GNAT
+   Name_Aft                            : constant Name_Id := N + 375;
+   Name_Alignment                      : constant Name_Id := N + 376;
+   Name_Asm_Input                      : constant Name_Id := N + 377; -- GNAT
+   Name_Asm_Output                     : constant Name_Id := N + 378; -- GNAT
+   Name_AST_Entry                      : constant Name_Id := N + 379; -- VMS
+   Name_Bit                            : constant Name_Id := N + 380; -- GNAT
+   Name_Bit_Order                      : constant Name_Id := N + 381;
+   Name_Bit_Position                   : constant Name_Id := N + 382; -- GNAT
+   Name_Body_Version                   : constant Name_Id := N + 383;
+   Name_Callable                       : constant Name_Id := N + 384;
+   Name_Caller                         : constant Name_Id := N + 385;
+   Name_Code_Address                   : constant Name_Id := N + 386; -- GNAT
+   Name_Component_Size                 : constant Name_Id := N + 387;
+   Name_Compose                        : constant Name_Id := N + 388;
+   Name_Constrained                    : constant Name_Id := N + 389;
+   Name_Count                          : constant Name_Id := N + 390;
+   Name_Default_Bit_Order              : constant Name_Id := N + 391; -- GNAT
+   Name_Definite                       : constant Name_Id := N + 392;
+   Name_Delta                          : constant Name_Id := N + 393;
+   Name_Denorm                         : constant Name_Id := N + 394;
+   Name_Digits                         : constant Name_Id := N + 395;
+   Name_Elaborated                     : constant Name_Id := N + 396; -- GNAT
+   Name_Emax                           : constant Name_Id := N + 397; -- Ada 83
+   Name_Enabled                        : constant Name_Id := N + 398; -- GNAT
+   Name_Enum_Rep                       : constant Name_Id := N + 399; -- GNAT
+   Name_Epsilon                        : constant Name_Id := N + 400; -- Ada 83
+   Name_Exponent                       : constant Name_Id := N + 401;
+   Name_External_Tag                   : constant Name_Id := N + 402;
+   Name_Fast_Math                      : constant Name_Id := N + 403; -- GNAT
+   Name_First                          : constant Name_Id := N + 404;
+   Name_First_Bit                      : constant Name_Id := N + 405;
+   Name_Fixed_Value                    : constant Name_Id := N + 406; -- GNAT
+   Name_Fore                           : constant Name_Id := N + 407;
+   Name_Has_Access_Values              : constant Name_Id := N + 408; -- GNAT
+   Name_Has_Discriminants              : constant Name_Id := N + 409; -- GNAT
+   Name_Identity                       : constant Name_Id := N + 410;
+   Name_Img                            : constant Name_Id := N + 411; -- GNAT
+   Name_Integer_Value                  : constant Name_Id := N + 412; -- GNAT
+   Name_Large                          : constant Name_Id := N + 413; -- Ada 83
+   Name_Last                           : constant Name_Id := N + 414;
+   Name_Last_Bit                       : constant Name_Id := N + 415;
+   Name_Leading_Part                   : constant Name_Id := N + 416;
+   Name_Length                         : constant Name_Id := N + 417;
+   Name_Machine_Emax                   : constant Name_Id := N + 418;
+   Name_Machine_Emin                   : constant Name_Id := N + 419;
+   Name_Machine_Mantissa               : constant Name_Id := N + 420;
+   Name_Machine_Overflows              : constant Name_Id := N + 421;
+   Name_Machine_Radix                  : constant Name_Id := N + 422;
+   Name_Machine_Rounding               : constant Name_Id := N + 423; -- Ada 05
+   Name_Machine_Rounds                 : constant Name_Id := N + 424;
+   Name_Machine_Size                   : constant Name_Id := N + 425; -- GNAT
+   Name_Mantissa                       : constant Name_Id := N + 426; -- Ada 83
+   Name_Max_Size_In_Storage_Elements   : constant Name_Id := N + 427;
+   Name_Maximum_Alignment              : constant Name_Id := N + 428; -- GNAT
+   Name_Mechanism_Code                 : constant Name_Id := N + 429; -- GNAT
+   Name_Mod                            : constant Name_Id := N + 430; -- Ada 05
+   Name_Model_Emin                     : constant Name_Id := N + 431;
+   Name_Model_Epsilon                  : constant Name_Id := N + 432;
+   Name_Model_Mantissa                 : constant Name_Id := N + 433;
+   Name_Model_Small                    : constant Name_Id := N + 434;
+   Name_Modulus                        : constant Name_Id := N + 435;
+   Name_Null_Parameter                 : constant Name_Id := N + 436; -- GNAT
+   Name_Object_Size                    : constant Name_Id := N + 437; -- GNAT
+   Name_Old                            : constant Name_Id := N + 438; -- GNAT
+   Name_Partition_ID                   : constant Name_Id := N + 439;
+   Name_Passed_By_Reference            : constant Name_Id := N + 440; -- GNAT
+   Name_Pool_Address                   : constant Name_Id := N + 441;
+   Name_Pos                            : constant Name_Id := N + 442;
+   Name_Position                       : constant Name_Id := N + 443;
+   Name_Priority                       : constant Name_Id := N + 444; -- Ada 05
+   Name_Range                          : constant Name_Id := N + 445;
+   Name_Range_Length                   : constant Name_Id := N + 446; -- GNAT
+   Name_Round                          : constant Name_Id := N + 447;
+   Name_Safe_Emax                      : constant Name_Id := N + 448; -- Ada 83
+   Name_Safe_First                     : constant Name_Id := N + 449;
+   Name_Safe_Large                     : constant Name_Id := N + 450; -- Ada 83
+   Name_Safe_Last                      : constant Name_Id := N + 451;
+   Name_Safe_Small                     : constant Name_Id := N + 452; -- Ada 83
+   Name_Scale                          : constant Name_Id := N + 453;
+   Name_Scaling                        : constant Name_Id := N + 454;
+   Name_Signed_Zeros                   : constant Name_Id := N + 455;
+   Name_Size                           : constant Name_Id := N + 456;
+   Name_Small                          : constant Name_Id := N + 457;
+   Name_Storage_Size                   : constant Name_Id := N + 458;
+   Name_Storage_Unit                   : constant Name_Id := N + 459; -- GNAT
+   Name_Stream_Size                    : constant Name_Id := N + 460; -- Ada 05
+   Name_Tag                            : constant Name_Id := N + 461;
+   Name_Target_Name                    : constant Name_Id := N + 462; -- GNAT
+   Name_Terminated                     : constant Name_Id := N + 463;
+   Name_To_Address                     : constant Name_Id := N + 464; -- GNAT
+   Name_Type_Class                     : constant Name_Id := N + 465; -- GNAT
+   Name_UET_Address                    : constant Name_Id := N + 466; -- GNAT
+   Name_Unbiased_Rounding              : constant Name_Id := N + 467;
+   Name_Unchecked_Access               : constant Name_Id := N + 468;
+   Name_Unconstrained_Array            : constant Name_Id := N + 469;
+   Name_Universal_Literal_String       : constant Name_Id := N + 470; -- GNAT
+   Name_Unrestricted_Access            : constant Name_Id := N + 471; -- GNAT
+   Name_VADS_Size                      : constant Name_Id := N + 472; -- GNAT
+   Name_Val                            : constant Name_Id := N + 473;
+   Name_Valid                          : constant Name_Id := N + 474;
+   Name_Value_Size                     : constant Name_Id := N + 475; -- GNAT
+   Name_Version                        : constant Name_Id := N + 476;
+   Name_Wchar_T_Size                   : constant Name_Id := N + 477; -- GNAT
+   Name_Wide_Wide_Width                : constant Name_Id := N + 478; -- Ada 05
+   Name_Wide_Width                     : constant Name_Id := N + 479;
+   Name_Width                          : constant Name_Id := N + 480;
+   Name_Word_Size                      : constant Name_Id := N + 481; -- GNAT
 
    --  Attributes that designate attributes returning renamable functions,
    --  i.e. functions that return other than a universal value and that
    --  have non-universal arguments.
 
-   First_Renamable_Function_Attribute  : constant Name_Id := N + 480;
-   Name_Adjacent                       : constant Name_Id := N + 480;
-   Name_Ceiling                        : constant Name_Id := N + 481;
-   Name_Copy_Sign                      : constant Name_Id := N + 482;
-   Name_Floor                          : constant Name_Id := N + 483;
-   Name_Fraction                       : constant Name_Id := N + 484;
-   Name_Image                          : constant Name_Id := N + 485;
-   Name_Input                          : constant Name_Id := N + 486;
-   Name_Machine                        : constant Name_Id := N + 487;
-   Name_Max                            : constant Name_Id := N + 488;
-   Name_Min                            : constant Name_Id := N + 489;
-   Name_Model                          : constant Name_Id := N + 490;
-   Name_Pred                           : constant Name_Id := N + 491;
-   Name_Remainder                      : constant Name_Id := N + 492;
-   Name_Rounding                       : constant Name_Id := N + 493;
-   Name_Succ                           : constant Name_Id := N + 494;
-   Name_Truncation                     : constant Name_Id := N + 495;
-   Name_Value                          : constant Name_Id := N + 496;
-   Name_Wide_Image                     : constant Name_Id := N + 497;
-   Name_Wide_Wide_Image                : constant Name_Id := N + 498;
-   Name_Wide_Value                     : constant Name_Id := N + 499;
-   Name_Wide_Wide_Value                : constant Name_Id := N + 500;
-   Last_Renamable_Function_Attribute   : constant Name_Id := N + 500;
+   First_Renamable_Function_Attribute  : constant Name_Id := N + 482;
+   Name_Adjacent                       : constant Name_Id := N + 482;
+   Name_Ceiling                        : constant Name_Id := N + 483;
+   Name_Copy_Sign                      : constant Name_Id := N + 484;
+   Name_Floor                          : constant Name_Id := N + 485;
+   Name_Fraction                       : constant Name_Id := N + 486;
+   Name_Image                          : constant Name_Id := N + 487;
+   Name_Input                          : constant Name_Id := N + 488;
+   Name_Machine                        : constant Name_Id := N + 489;
+   Name_Max                            : constant Name_Id := N + 490;
+   Name_Min                            : constant Name_Id := N + 491;
+   Name_Model                          : constant Name_Id := N + 492;
+   Name_Pred                           : constant Name_Id := N + 493;
+   Name_Remainder                      : constant Name_Id := N + 494;
+   Name_Rounding                       : constant Name_Id := N + 495;
+   Name_Succ                           : constant Name_Id := N + 496;
+   Name_Truncation                     : constant Name_Id := N + 497;
+   Name_Value                          : constant Name_Id := N + 498;
+   Name_Wide_Image                     : constant Name_Id := N + 499;
+   Name_Wide_Wide_Image                : constant Name_Id := N + 500;
+   Name_Wide_Value                     : constant Name_Id := N + 501;
+   Name_Wide_Wide_Value                : constant Name_Id := N + 502;
+   Last_Renamable_Function_Attribute   : constant Name_Id := N + 502;
 
    --  Attributes that designate procedures
 
-   First_Procedure_Attribute           : constant Name_Id := N + 501;
-   Name_Output                         : constant Name_Id := N + 501;
-   Name_Read                           : constant Name_Id := N + 502;
-   Name_Write                          : constant Name_Id := N + 503;
-   Last_Procedure_Attribute            : constant Name_Id := N + 503;
+   First_Procedure_Attribute           : constant Name_Id := N + 503;
+   Name_Output                         : constant Name_Id := N + 503;
+   Name_Read                           : constant Name_Id := N + 504;
+   Name_Write                          : constant Name_Id := N + 505;
+   Last_Procedure_Attribute            : constant Name_Id := N + 505;
 
    --  Remaining attributes are ones that return entities
 
-   First_Entity_Attribute_Name         : constant Name_Id := N + 504;
-   Name_Elab_Body                      : constant Name_Id := N + 504; -- GNAT
-   Name_Elab_Spec                      : constant Name_Id := N + 505; -- GNAT
-   Name_Storage_Pool                   : constant Name_Id := N + 506;
+   First_Entity_Attribute_Name         : constant Name_Id := N + 506;
+   Name_Elab_Body                      : constant Name_Id := N + 506; -- GNAT
+   Name_Elab_Spec                      : constant Name_Id := N + 507; -- GNAT
+   Name_Storage_Pool                   : constant Name_Id := N + 508;
 
    --  These attributes are the ones that return types
 
-   First_Type_Attribute_Name           : constant Name_Id := N + 507;
-   Name_Base                           : constant Name_Id := N + 507;
-   Name_Class                          : constant Name_Id := N + 508;
-   Name_Stub_Type                      : constant Name_Id := N + 509;
-   Last_Type_Attribute_Name            : constant Name_Id := N + 509;
-   Last_Entity_Attribute_Name          : constant Name_Id := N + 509;
-   Last_Attribute_Name                 : constant Name_Id := N + 509;
+   First_Type_Attribute_Name           : constant Name_Id := N + 509;
+   Name_Base                           : constant Name_Id := N + 509;
+   Name_Class                          : constant Name_Id := N + 510;
+   Name_Stub_Type                      : constant Name_Id := N + 511;
+   Last_Type_Attribute_Name            : constant Name_Id := N + 511;
+   Last_Entity_Attribute_Name          : constant Name_Id := N + 511;
+   Last_Attribute_Name                 : constant Name_Id := N + 511;
 
    --  Names of recognized locking policy identifiers
 
@@ -834,10 +836,10 @@ package Snames is
    --  name (e.g. C for Ceiling_Locking). If new policy names are added,
    --  the first character must be distinct.
 
-   First_Locking_Policy_Name           : constant Name_Id := N + 510;
-   Name_Ceiling_Locking                : constant Name_Id := N + 510;
-   Name_Inheritance_Locking            : constant Name_Id := N + 511;
-   Last_Locking_Policy_Name            : constant Name_Id := N + 511;
+   First_Locking_Policy_Name           : constant Name_Id := N + 512;
+   Name_Ceiling_Locking                : constant Name_Id := N + 512;
+   Name_Inheritance_Locking            : constant Name_Id := N + 513;
+   Last_Locking_Policy_Name            : constant Name_Id := N + 513;
 
    --  Names of recognized queuing policy identifiers
 
@@ -845,10 +847,10 @@ package Snames is
    --  name (e.g. F for FIFO_Queuing). If new policy names are added,
    --  the first character must be distinct.
 
-   First_Queuing_Policy_Name           : constant Name_Id := N + 512;
-   Name_FIFO_Queuing                   : constant Name_Id := N + 512;
-   Name_Priority_Queuing               : constant Name_Id := N + 513;
-   Last_Queuing_Policy_Name            : constant Name_Id := N + 513;
+   First_Queuing_Policy_Name           : constant Name_Id := N + 514;
+   Name_FIFO_Queuing                   : constant Name_Id := N + 514;
+   Name_Priority_Queuing               : constant Name_Id := N + 515;
+   Last_Queuing_Policy_Name            : constant Name_Id := N + 515;
 
    --  Names of recognized task dispatching policy identifiers
 
@@ -856,273 +858,275 @@ package Snames is
    --  name (e.g. F for FIFO_Within_Priorities). If new policy names
    --  are added, the first character must be distinct.
 
-   First_Task_Dispatching_Policy_Name  : constant Name_Id := N + 514;
-   Name_EDF_Across_Priorities          : constant Name_Id := N + 514;
-   Name_FIFO_Within_Priorities         : constant Name_Id := N + 515;
+   First_Task_Dispatching_Policy_Name  : constant Name_Id := N + 516;
+   Name_EDF_Across_Priorities          : constant Name_Id := N + 516;
+   Name_FIFO_Within_Priorities         : constant Name_Id := N + 517;
    Name_Non_Preemptive_Within_Priorities
                                        : constant Name_Id := N + 513;
-   Name_Round_Robin_Within_Priorities  : constant Name_Id := N + 516;
-   Last_Task_Dispatching_Policy_Name   : constant Name_Id := N + 516;
+   Name_Round_Robin_Within_Priorities  : constant Name_Id := N + 518;
+   Last_Task_Dispatching_Policy_Name   : constant Name_Id := N + 518;
 
    --  Names of recognized checks for pragma Suppress
 
-   First_Check_Name                    : constant Name_Id := N + 517;
-   Name_Access_Check                   : constant Name_Id := N + 517;
-   Name_Accessibility_Check            : constant Name_Id := N + 518;
-   Name_Alignment_Check                : constant Name_Id := N + 519; -- GNAT
-   Name_Discriminant_Check             : constant Name_Id := N + 520;
-   Name_Division_Check                 : constant Name_Id := N + 521;
-   Name_Elaboration_Check              : constant Name_Id := N + 522;
-   Name_Index_Check                    : constant Name_Id := N + 523;
-   Name_Length_Check                   : constant Name_Id := N + 524;
-   Name_Overflow_Check                 : constant Name_Id := N + 525;
-   Name_Range_Check                    : constant Name_Id := N + 526;
-   Name_Storage_Check                  : constant Name_Id := N + 527;
-   Name_Tag_Check                      : constant Name_Id := N + 528;
-   Name_Validity_Check                 : constant Name_Id := N + 529; -- GNAT
-   Name_All_Checks                     : constant Name_Id := N + 530;
-   Last_Check_Name                     : constant Name_Id := N + 530;
+   First_Check_Name                    : constant Name_Id := N + 519;
+   Name_Access_Check                   : constant Name_Id := N + 519;
+   Name_Accessibility_Check            : constant Name_Id := N + 520;
+   Name_Alignment_Check                : constant Name_Id := N + 521; -- GNAT
+   Name_Discriminant_Check             : constant Name_Id := N + 522;
+   Name_Division_Check                 : constant Name_Id := N + 523;
+   Name_Elaboration_Check              : constant Name_Id := N + 524;
+   Name_Index_Check                    : constant Name_Id := N + 525;
+   Name_Length_Check                   : constant Name_Id := N + 526;
+   Name_Overflow_Check                 : constant Name_Id := N + 527;
+   Name_Range_Check                    : constant Name_Id := N + 528;
+   Name_Storage_Check                  : constant Name_Id := N + 529;
+   Name_Tag_Check                      : constant Name_Id := N + 530;
+   Name_Validity_Check                 : constant Name_Id := N + 531; -- GNAT
+   Name_All_Checks                     : constant Name_Id := N + 532;
+   Last_Check_Name                     : constant Name_Id := N + 532;
 
    --  Names corresponding to reserved keywords, excluding those already
    --  declared in the attribute list (Access, Delta, Digits, Mod, Range).
 
-   Name_Abort                          : constant Name_Id := N + 531;
-   Name_Abs                            : constant Name_Id := N + 532;
-   Name_Accept                         : constant Name_Id := N + 533;
-   Name_And                            : constant Name_Id := N + 534;
-   Name_All                            : constant Name_Id := N + 535;
-   Name_Array                          : constant Name_Id := N + 536;
-   Name_At                             : constant Name_Id := N + 537;
-   Name_Begin                          : constant Name_Id := N + 538;
-   Name_Body                           : constant Name_Id := N + 539;
-   Name_Case                           : constant Name_Id := N + 540;
-   Name_Constant                       : constant Name_Id := N + 541;
-   Name_Declare                        : constant Name_Id := N + 542;
-   Name_Delay                          : constant Name_Id := N + 543;
-   Name_Do                             : constant Name_Id := N + 544;
-   Name_Else                           : constant Name_Id := N + 545;
-   Name_Elsif                          : constant Name_Id := N + 546;
-   Name_End                            : constant Name_Id := N + 547;
-   Name_Entry                          : constant Name_Id := N + 548;
-   Name_Exception                      : constant Name_Id := N + 549;
-   Name_Exit                           : constant Name_Id := N + 550;
-   Name_For                            : constant Name_Id := N + 551;
-   Name_Function                       : constant Name_Id := N + 552;
-   Name_Generic                        : constant Name_Id := N + 553;
-   Name_Goto                           : constant Name_Id := N + 554;
-   Name_If                             : constant Name_Id := N + 555;
-   Name_In                             : constant Name_Id := N + 556;
-   Name_Is                             : constant Name_Id := N + 557;
-   Name_Limited                        : constant Name_Id := N + 558;
-   Name_Loop                           : constant Name_Id := N + 559;
-   Name_New                            : constant Name_Id := N + 560;
-   Name_Not                            : constant Name_Id := N + 561;
-   Name_Null                           : constant Name_Id := N + 562;
-   Name_Of                             : constant Name_Id := N + 563;
-   Name_Or                             : constant Name_Id := N + 564;
-   Name_Others                         : constant Name_Id := N + 565;
-   Name_Out                            : constant Name_Id := N + 566;
-   Name_Package                        : constant Name_Id := N + 567;
-   Name_Pragma                         : constant Name_Id := N + 568;
-   Name_Private                        : constant Name_Id := N + 569;
-   Name_Procedure                      : constant Name_Id := N + 570;
-   Name_Raise                          : constant Name_Id := N + 571;
-   Name_Record                         : constant Name_Id := N + 572;
-   Name_Rem                            : constant Name_Id := N + 573;
-   Name_Renames                        : constant Name_Id := N + 574;
-   Name_Return                         : constant Name_Id := N + 575;
-   Name_Reverse                        : constant Name_Id := N + 576;
-   Name_Select                         : constant Name_Id := N + 577;
-   Name_Separate                       : constant Name_Id := N + 578;
-   Name_Subtype                        : constant Name_Id := N + 579;
-   Name_Task                           : constant Name_Id := N + 580;
-   Name_Terminate                      : constant Name_Id := N + 581;
-   Name_Then                           : constant Name_Id := N + 582;
-   Name_Type                           : constant Name_Id := N + 583;
-   Name_Use                            : constant Name_Id := N + 584;
-   Name_When                           : constant Name_Id := N + 585;
-   Name_While                          : constant Name_Id := N + 586;
-   Name_With                           : constant Name_Id := N + 587;
-   Name_Xor                            : constant Name_Id := N + 588;
+   Name_Abort                          : constant Name_Id := N + 533;
+   Name_Abs                            : constant Name_Id := N + 534;
+   Name_Accept                         : constant Name_Id := N + 535;
+   Name_And                            : constant Name_Id := N + 536;
+   Name_All                            : constant Name_Id := N + 537;
+   Name_Array                          : constant Name_Id := N + 538;
+   Name_At                             : constant Name_Id := N + 539;
+   Name_Begin                          : constant Name_Id := N + 540;
+   Name_Body                           : constant Name_Id := N + 541;
+   Name_Case                           : constant Name_Id := N + 542;
+   Name_Constant                       : constant Name_Id := N + 543;
+   Name_Declare                        : constant Name_Id := N + 544;
+   Name_Delay                          : constant Name_Id := N + 545;
+   Name_Do                             : constant Name_Id := N + 546;
+   Name_Else                           : constant Name_Id := N + 547;
+   Name_Elsif                          : constant Name_Id := N + 548;
+   Name_End                            : constant Name_Id := N + 549;
+   Name_Entry                          : constant Name_Id := N + 550;
+   Name_Exception                      : constant Name_Id := N + 551;
+   Name_Exit                           : constant Name_Id := N + 552;
+   Name_For                            : constant Name_Id := N + 553;
+   Name_Function                       : constant Name_Id := N + 554;
+   Name_Generic                        : constant Name_Id := N + 555;
+   Name_Goto                           : constant Name_Id := N + 556;
+   Name_If                             : constant Name_Id := N + 557;
+   Name_In                             : constant Name_Id := N + 558;
+   Name_Is                             : constant Name_Id := N + 559;
+   Name_Limited                        : constant Name_Id := N + 560;
+   Name_Loop                           : constant Name_Id := N + 561;
+   Name_New                            : constant Name_Id := N + 562;
+   Name_Not                            : constant Name_Id := N + 563;
+   Name_Null                           : constant Name_Id := N + 564;
+   Name_Of                             : constant Name_Id := N + 565;
+   Name_Or                             : constant Name_Id := N + 566;
+   Name_Others                         : constant Name_Id := N + 567;
+   Name_Out                            : constant Name_Id := N + 568;
+   Name_Package                        : constant Name_Id := N + 569;
+   Name_Pragma                         : constant Name_Id := N + 570;
+   Name_Private                        : constant Name_Id := N + 571;
+   Name_Procedure                      : constant Name_Id := N + 572;
+   Name_Raise                          : constant Name_Id := N + 573;
+   Name_Record                         : constant Name_Id := N + 574;
+   Name_Rem                            : constant Name_Id := N + 575;
+   Name_Renames                        : constant Name_Id := N + 576;
+   Name_Return                         : constant Name_Id := N + 577;
+   Name_Reverse                        : constant Name_Id := N + 578;
+   Name_Select                         : constant Name_Id := N + 579;
+   Name_Separate                       : constant Name_Id := N + 580;
+   Name_Subtype                        : constant Name_Id := N + 581;
+   Name_Task                           : constant Name_Id := N + 582;
+   Name_Terminate                      : constant Name_Id := N + 583;
+   Name_Then                           : constant Name_Id := N + 584;
+   Name_Type                           : constant Name_Id := N + 585;
+   Name_Use                            : constant Name_Id := N + 586;
+   Name_When                           : constant Name_Id := N + 587;
+   Name_While                          : constant Name_Id := N + 588;
+   Name_With                           : constant Name_Id := N + 589;
+   Name_Xor                            : constant Name_Id := N + 590;
 
    --  Names of intrinsic subprograms
 
    --  Note: Asm is missing from this list, since Asm is a legitimate
    --  convention name. So is To_Adress, which is a GNAT attribute.
 
-   First_Intrinsic_Name                 : constant Name_Id := N + 589;
-   Name_Divide                          : constant Name_Id := N + 589;
-   Name_Enclosing_Entity                : constant Name_Id := N + 590;
-   Name_Exception_Information           : constant Name_Id := N + 591;
-   Name_Exception_Message               : constant Name_Id := N + 592;
-   Name_Exception_Name                  : constant Name_Id := N + 593;
-   Name_File                            : constant Name_Id := N + 594;
-   Name_Generic_Dispatching_Constructor : constant Name_Id := N + 595;
-   Name_Import_Address                  : constant Name_Id := N + 596;
-   Name_Import_Largest_Value            : constant Name_Id := N + 597;
-   Name_Import_Value                    : constant Name_Id := N + 598;
-   Name_Is_Negative                     : constant Name_Id := N + 599;
-   Name_Line                            : constant Name_Id := N + 600;
-   Name_Rotate_Left                     : constant Name_Id := N + 601;
-   Name_Rotate_Right                    : constant Name_Id := N + 602;
-   Name_Shift_Left                      : constant Name_Id := N + 603;
-   Name_Shift_Right                     : constant Name_Id := N + 604;
-   Name_Shift_Right_Arithmetic          : constant Name_Id := N + 605;
-   Name_Source_Location                 : constant Name_Id := N + 606;
-   Name_Unchecked_Conversion            : constant Name_Id := N + 607;
-   Name_Unchecked_Deallocation          : constant Name_Id := N + 608;
-   Name_To_Pointer                      : constant Name_Id := N + 609;
-   Last_Intrinsic_Name                  : constant Name_Id := N + 609;
+   First_Intrinsic_Name                 : constant Name_Id := N + 591;
+   Name_Divide                          : constant Name_Id := N + 591;
+   Name_Enclosing_Entity                : constant Name_Id := N + 592;
+   Name_Exception_Information           : constant Name_Id := N + 593;
+   Name_Exception_Message               : constant Name_Id := N + 594;
+   Name_Exception_Name                  : constant Name_Id := N + 595;
+   Name_File                            : constant Name_Id := N + 596;
+   Name_Generic_Dispatching_Constructor : constant Name_Id := N + 597;
+   Name_Import_Address                  : constant Name_Id := N + 598;
+   Name_Import_Largest_Value            : constant Name_Id := N + 599;
+   Name_Import_Value                    : constant Name_Id := N + 600;
+   Name_Is_Negative                     : constant Name_Id := N + 601;
+   Name_Line                            : constant Name_Id := N + 602;
+   Name_Rotate_Left                     : constant Name_Id := N + 603;
+   Name_Rotate_Right                    : constant Name_Id := N + 604;
+   Name_Shift_Left                      : constant Name_Id := N + 605;
+   Name_Shift_Right                     : constant Name_Id := N + 606;
+   Name_Shift_Right_Arithmetic          : constant Name_Id := N + 607;
+   Name_Source_Location                 : constant Name_Id := N + 608;
+   Name_Unchecked_Conversion            : constant Name_Id := N + 609;
+   Name_Unchecked_Deallocation          : constant Name_Id := N + 610;
+   Name_To_Pointer                      : constant Name_Id := N + 611;
+   Last_Intrinsic_Name                  : constant Name_Id := N + 611;
 
    --  Names used in processing intrinsic calls
 
-   Name_Free                           : constant Name_Id := N + 610;
+   Name_Free                           : constant Name_Id := N + 612;
 
    --  Reserved words used only in Ada 95
 
-   First_95_Reserved_Word              : constant Name_Id := N + 611;
-   Name_Abstract                       : constant Name_Id := N + 611;
-   Name_Aliased                        : constant Name_Id := N + 612;
-   Name_Protected                      : constant Name_Id := N + 613;
-   Name_Until                          : constant Name_Id := N + 614;
-   Name_Requeue                        : constant Name_Id := N + 615;
-   Name_Tagged                         : constant Name_Id := N + 616;
-   Last_95_Reserved_Word               : constant Name_Id := N + 616;
+   First_95_Reserved_Word              : constant Name_Id := N + 613;
+   Name_Abstract                       : constant Name_Id := N + 613;
+   Name_Aliased                        : constant Name_Id := N + 614;
+   Name_Protected                      : constant Name_Id := N + 615;
+   Name_Until                          : constant Name_Id := N + 616;
+   Name_Requeue                        : constant Name_Id := N + 617;
+   Name_Tagged                         : constant Name_Id := N + 618;
+   Last_95_Reserved_Word               : constant Name_Id := N + 618;
 
    subtype Ada_95_Reserved_Words is
      Name_Id range First_95_Reserved_Word .. Last_95_Reserved_Word;
 
    --  Miscellaneous names used in semantic checking
 
-   Name_Raise_Exception                : constant Name_Id := N + 617;
+   Name_Raise_Exception                : constant Name_Id := N + 619;
 
    --  Additional reserved words and identifiers used in GNAT Project Files
    --  Note that Name_External is already previously declared
 
-   Name_Ada_Roots                      : constant Name_Id := N + 618;
-   Name_Archive_Builder                : constant Name_Id := N + 619;
-   Name_Archive_Indexer                : constant Name_Id := N + 620;
-   Name_Archive_Suffix                 : constant Name_Id := N + 621;
-   Name_Binder                         : constant Name_Id := N + 622;
-   Name_Binder_Prefix                  : constant Name_Id := N + 623;
-   Name_Body_Suffix                    : constant Name_Id := N + 624;
-   Name_Builder                        : constant Name_Id := N + 625;
-   Name_Builder_Switches               : constant Name_Id := N + 626;
-   Name_Compiler                       : constant Name_Id := N + 627;
-   Name_Compiler_Kind                  : constant Name_Id := N + 628;
-   Name_Config_Body_File_Name          : constant Name_Id := N + 629;
-   Name_Config_Body_File_Name_Pattern  : constant Name_Id := N + 630;
-   Name_Config_File_Switches           : constant Name_Id := N + 631;
-   Name_Config_File_Unique             : constant Name_Id := N + 632;
-   Name_Config_Spec_File_Name          : constant Name_Id := N + 633;
-   Name_Config_Spec_File_Name_Pattern  : constant Name_Id := N + 634;
-   Name_Cross_Reference                : constant Name_Id := N + 635;
-   Name_Default_Language               : constant Name_Id := N + 636;
-   Name_Default_Switches               : constant Name_Id := N + 637;
-   Name_Dependency_Driver              : constant Name_Id := N + 638;
-   Name_Dependency_File_Kind           : constant Name_Id := N + 639;
-   Name_Dependency_Switches            : constant Name_Id := N + 640;
-   Name_Driver                         : constant Name_Id := N + 641;
-   Name_Excluded_Source_Dirs           : constant Name_Id := N + 642;
-   Name_Excluded_Source_Files          : constant Name_Id := N + 643;
-   Name_Exec_Dir                       : constant Name_Id := N + 644;
-   Name_Executable                     : constant Name_Id := N + 645;
-   Name_Executable_Suffix              : constant Name_Id := N + 646;
-   Name_Extends                        : constant Name_Id := N + 647;
-   Name_Externally_Built               : constant Name_Id := N + 648;
-   Name_Finder                         : constant Name_Id := N + 649;
-   Name_Global_Configuration_Pragmas   : constant Name_Id := N + 650;
-   Name_Global_Config_File             : constant Name_Id := N + 651;
-   Name_Gnatls                         : constant Name_Id := N + 652;
-   Name_Gnatstub                       : constant Name_Id := N + 653;
-   Name_Implementation                 : constant Name_Id := N + 654;
-   Name_Implementation_Exceptions      : constant Name_Id := N + 655;
-   Name_Implementation_Suffix          : constant Name_Id := N + 656;
-   Name_Include_Switches               : constant Name_Id := N + 657;
-   Name_Include_Path                   : constant Name_Id := N + 658;
-   Name_Include_Path_File              : constant Name_Id := N + 659;
-   Name_Language_Kind                  : constant Name_Id := N + 660;
-   Name_Language_Processing            : constant Name_Id := N + 661;
-   Name_Languages                      : constant Name_Id := N + 662;
-   Name_Library_Ali_Dir                : constant Name_Id := N + 663;
-   Name_Library_Auto_Init              : constant Name_Id := N + 664;
-   Name_Library_Auto_Init_Supported    : constant Name_Id := N + 665;
-   Name_Library_Builder                : constant Name_Id := N + 666;
-   Name_Library_Dir                    : constant Name_Id := N + 667;
-   Name_Library_GCC                    : constant Name_Id := N + 668;
-   Name_Library_Interface              : constant Name_Id := N + 669;
-   Name_Library_Kind                   : constant Name_Id := N + 670;
-   Name_Library_Name                   : constant Name_Id := N + 671;
-   Name_Library_Major_Minor_Id_Supported : constant Name_Id := N + 672;
-   Name_Library_Options                : constant Name_Id := N + 673;
-   Name_Library_Partial_Linker         : constant Name_Id := N + 674;
-   Name_Library_Reference_Symbol_File  : constant Name_Id := N + 675;
-   Name_Library_Src_Dir                : constant Name_Id := N + 676;
-   Name_Library_Support                : constant Name_Id := N + 677;
-   Name_Library_Symbol_File            : constant Name_Id := N + 678;
-   Name_Library_Symbol_Policy          : constant Name_Id := N + 679;
-   Name_Library_Version                : constant Name_Id := N + 680;
-   Name_Library_Version_Switches       : constant Name_Id := N + 681;
-   Name_Linker                         : constant Name_Id := N + 682;
-   Name_Linker_Executable_Option       : constant Name_Id := N + 683;
-   Name_Linker_Lib_Dir_Option          : constant Name_Id := N + 684;
-   Name_Linker_Lib_Name_Option         : constant Name_Id := N + 685;
-   Name_Local_Config_File              : constant Name_Id := N + 686;
-   Name_Local_Configuration_Pragmas    : constant Name_Id := N + 687;
-   Name_Locally_Removed_Files          : constant Name_Id := N + 688;
-   Name_Mapping_File_Switches          : constant Name_Id := N + 689;
-   Name_Mapping_Spec_Suffix            : constant Name_Id := N + 690;
-   Name_Mapping_Body_Suffix            : constant Name_Id := N + 691;
-   Name_Metrics                        : constant Name_Id := N + 692;
-   Name_Naming                         : constant Name_Id := N + 693;
-   Name_Objects_Path                   : constant Name_Id := N + 694;
-   Name_Objects_Path_File              : constant Name_Id := N + 695;
-   Name_Object_Dir                     : constant Name_Id := N + 696;
-   Name_Pic_Option                     : constant Name_Id := N + 697;
-   Name_Pretty_Printer                 : constant Name_Id := N + 698;
-   Name_Prefix                         : constant Name_Id := N + 699;
-   Name_Project                        : constant Name_Id := N + 700;
-   Name_Roots                          : constant Name_Id := N + 701;
-   Name_Required_Switches              : constant Name_Id := N + 702;
-   Name_Run_Path_Option                : constant Name_Id := N + 703;
-   Name_Runtime_Project                : constant Name_Id := N + 704;
-   Name_Shared_Library_Minimum_Switches : constant Name_Id := N + 705;
-   Name_Shared_Library_Prefix          : constant Name_Id := N + 706;
-   Name_Shared_Library_Suffix          : constant Name_Id := N + 707;
-   Name_Separate_Suffix                : constant Name_Id := N + 708;
-   Name_Source_Dirs                    : constant Name_Id := N + 709;
-   Name_Source_Files                   : constant Name_Id := N + 710;
-   Name_Source_List_File               : constant Name_Id := N + 711;
-   Name_Spec                           : constant Name_Id := N + 712;
-   Name_Spec_Suffix                    : constant Name_Id := N + 713;
-   Name_Specification                  : constant Name_Id := N + 714;
-   Name_Specification_Exceptions       : constant Name_Id := N + 715;
-   Name_Specification_Suffix           : constant Name_Id := N + 716;
-   Name_Stack                          : constant Name_Id := N + 717;
-   Name_Switches                       : constant Name_Id := N + 718;
-   Name_Symbolic_Link_Supported        : constant Name_Id := N + 719;
-   Name_Toolchain_Description          : constant Name_Id := N + 720;
-   Name_Toolchain_Version              : constant Name_Id := N + 721;
-   Name_Runtime_Library_Dir            : constant Name_Id := N + 722;
+   Name_Ada_Roots                      : constant Name_Id := N + 620;
+   Name_Archive_Builder                : constant Name_Id := N + 621;
+   Name_Archive_Indexer                : constant Name_Id := N + 622;
+   Name_Archive_Suffix                 : constant Name_Id := N + 623;
+   Name_Binder                         : constant Name_Id := N + 624;
+   Name_Binder_Prefix                  : constant Name_Id := N + 625;
+   Name_Body_Suffix                    : constant Name_Id := N + 626;
+   Name_Builder                        : constant Name_Id := N + 627;
+   Name_Builder_Switches               : constant Name_Id := N + 628;
+   Name_Compiler                       : constant Name_Id := N + 629;
+   Name_Compiler_Kind                  : constant Name_Id := N + 630;
+   Name_Config_Body_File_Name          : constant Name_Id := N + 631;
+   Name_Config_Body_File_Name_Pattern  : constant Name_Id := N + 632;
+   Name_Config_File_Switches           : constant Name_Id := N + 633;
+   Name_Config_File_Unique             : constant Name_Id := N + 634;
+   Name_Config_Spec_File_Name          : constant Name_Id := N + 635;
+   Name_Config_Spec_File_Name_Pattern  : constant Name_Id := N + 636;
+   Name_Cross_Reference                : constant Name_Id := N + 637;
+   Name_Default_Language               : constant Name_Id := N + 638;
+   Name_Default_Switches               : constant Name_Id := N + 639;
+   Name_Dependency_Driver              : constant Name_Id := N + 640;
+   Name_Dependency_File_Kind           : constant Name_Id := N + 641;
+   Name_Dependency_Switches            : constant Name_Id := N + 642;
+   Name_Driver                         : constant Name_Id := N + 643;
+   Name_Excluded_Source_Dirs           : constant Name_Id := N + 644;
+   Name_Excluded_Source_Files          : constant Name_Id := N + 645;
+   Name_Exec_Dir                       : constant Name_Id := N + 646;
+   Name_Executable                     : constant Name_Id := N + 647;
+   Name_Executable_Suffix              : constant Name_Id := N + 648;
+   Name_Extends                        : constant Name_Id := N + 649;
+   Name_Externally_Built               : constant Name_Id := N + 650;
+   Name_Finder                         : constant Name_Id := N + 651;
+   Name_Global_Configuration_Pragmas   : constant Name_Id := N + 652;
+   Name_Global_Config_File             : constant Name_Id := N + 653;
+   Name_Gnatls                         : constant Name_Id := N + 654;
+   Name_Gnatstub                       : constant Name_Id := N + 655;
+   Name_Implementation                 : constant Name_Id := N + 656;
+   Name_Implementation_Exceptions      : constant Name_Id := N + 657;
+   Name_Implementation_Suffix          : constant Name_Id := N + 658;
+   Name_Include_Switches               : constant Name_Id := N + 659;
+   Name_Include_Path                   : constant Name_Id := N + 660;
+   Name_Include_Path_File              : constant Name_Id := N + 661;
+   Name_Language_Kind                  : constant Name_Id := N + 662;
+   Name_Language_Processing            : constant Name_Id := N + 663;
+   Name_Languages                      : constant Name_Id := N + 664;
+   Name_Library_Ali_Dir                : constant Name_Id := N + 665;
+   Name_Library_Auto_Init              : constant Name_Id := N + 666;
+   Name_Library_Auto_Init_Supported    : constant Name_Id := N + 667;
+   Name_Library_Builder                : constant Name_Id := N + 668;
+   Name_Library_Dir                    : constant Name_Id := N + 669;
+   Name_Library_GCC                    : constant Name_Id := N + 670;
+   Name_Library_Interface              : constant Name_Id := N + 671;
+   Name_Library_Kind                   : constant Name_Id := N + 672;
+   Name_Library_Name                   : constant Name_Id := N + 673;
+   Name_Library_Major_Minor_Id_Supported : constant Name_Id := N + 674;
+   Name_Library_Options                : constant Name_Id := N + 675;
+   Name_Library_Partial_Linker         : constant Name_Id := N + 676;
+   Name_Library_Reference_Symbol_File  : constant Name_Id := N + 677;
+   Name_Library_Src_Dir                : constant Name_Id := N + 678;
+   Name_Library_Support                : constant Name_Id := N + 679;
+   Name_Library_Symbol_File            : constant Name_Id := N + 680;
+   Name_Library_Symbol_Policy          : constant Name_Id := N + 681;
+   Name_Library_Version                : constant Name_Id := N + 682;
+   Name_Library_Version_Switches       : constant Name_Id := N + 683;
+   Name_Linker                         : constant Name_Id := N + 684;
+   Name_Linker_Executable_Option       : constant Name_Id := N + 685;
+   Name_Linker_Lib_Dir_Option          : constant Name_Id := N + 686;
+   Name_Linker_Lib_Name_Option         : constant Name_Id := N + 687;
+   Name_Local_Config_File              : constant Name_Id := N + 688;
+   Name_Local_Configuration_Pragmas    : constant Name_Id := N + 689;
+   Name_Locally_Removed_Files          : constant Name_Id := N + 690;
+   Name_Mapping_File_Switches          : constant Name_Id := N + 691;
+   Name_Mapping_Spec_Suffix            : constant Name_Id := N + 692;
+   Name_Mapping_Body_Suffix            : constant Name_Id := N + 693;
+   Name_Metrics                        : constant Name_Id := N + 694;
+   Name_Naming                         : constant Name_Id := N + 695;
+   Name_Objects_Path                   : constant Name_Id := N + 696;
+   Name_Objects_Path_File              : constant Name_Id := N + 697;
+   Name_Object_Dir                     : constant Name_Id := N + 698;
+   Name_Pic_Option                     : constant Name_Id := N + 699;
+   Name_Pretty_Printer                 : constant Name_Id := N + 700;
+   Name_Prefix                         : constant Name_Id := N + 701;
+   Name_Project                        : constant Name_Id := N + 702;
+   Name_Roots                          : constant Name_Id := N + 703;
+   Name_Required_Switches              : constant Name_Id := N + 704;
+   Name_Run_Path_Option                : constant Name_Id := N + 705;
+   Name_Runtime_Project                : constant Name_Id := N + 706;
+   Name_Shared_Library_Minimum_Switches : constant Name_Id := N + 707;
+   Name_Shared_Library_Prefix          : constant Name_Id := N + 708;
+   Name_Shared_Library_Suffix          : constant Name_Id := N + 709;
+   Name_Separate_Suffix                : constant Name_Id := N + 710;
+   Name_Source_Dirs                    : constant Name_Id := N + 711;
+   Name_Source_Files                   : constant Name_Id := N + 712;
+   Name_Source_List_File               : constant Name_Id := N + 713;
+   Name_Spec                           : constant Name_Id := N + 714;
+   Name_Spec_Suffix                    : constant Name_Id := N + 715;
+   Name_Specification                  : constant Name_Id := N + 716;
+   Name_Specification_Exceptions       : constant Name_Id := N + 717;
+   Name_Specification_Suffix           : constant Name_Id := N + 718;
+   Name_Stack                          : constant Name_Id := N + 719;
+   Name_Switches                       : constant Name_Id := N + 720;
+   Name_Symbolic_Link_Supported        : constant Name_Id := N + 721;
+   Name_Sync                           : constant Name_Id := N + 722;
+   Name_Synchronize                    : constant Name_Id := N + 723;
+   Name_Toolchain_Description          : constant Name_Id := N + 724;
+   Name_Toolchain_Version              : constant Name_Id := N + 725;
+   Name_Runtime_Library_Dir            : constant Name_Id := N + 726;
 
    --  Other miscellaneous names used in front end
 
-   Name_Unaligned_Valid                : constant Name_Id := N + 723;
+   Name_Unaligned_Valid                : constant Name_Id := N + 727;
 
    --  Ada 2005 reserved words
 
-   First_2005_Reserved_Word            : constant Name_Id := N + 724;
-   Name_Interface                      : constant Name_Id := N + 724;
-   Name_Overriding                     : constant Name_Id := N + 725;
-   Name_Synchronized                   : constant Name_Id := N + 726;
-   Last_2005_Reserved_Word             : constant Name_Id := N + 726;
+   First_2005_Reserved_Word            : constant Name_Id := N + 728;
+   Name_Interface                      : constant Name_Id := N + 728;
+   Name_Overriding                     : constant Name_Id := N + 729;
+   Name_Synchronized                   : constant Name_Id := N + 730;
+   Last_2005_Reserved_Word             : constant Name_Id := N + 730;
 
    subtype Ada_2005_Reserved_Words is
      Name_Id range First_2005_Reserved_Word .. Last_2005_Reserved_Word;
 
    --  Mark last defined name for consistency check in Snames body
 
-   Last_Predefined_Name                : constant Name_Id := N + 726;
+   Last_Predefined_Name                : constant Name_Id := N + 730;
 
    ---------------------------------------
    -- Subtypes Defining Name Categories --
@@ -1206,6 +1210,7 @@ package Snames is
       Attribute_Modulus,
       Attribute_Null_Parameter,
       Attribute_Object_Size,
+      Attribute_Old,
       Attribute_Partition_ID,
       Attribute_Passed_By_Reference,
       Attribute_Pool_Address,
@@ -1292,6 +1297,9 @@ package Snames is
       Attribute_Class,
       Attribute_Stub_Type);
 
+   type Attribute_Class_Array is array (Attribute_Id) of Boolean;
+   --  Type used to build attribute classification flag arrays
+
    ------------------------------------
    -- Convention Name ID Definitions --
    ------------------------------------
@@ -1376,6 +1384,7 @@ package Snames is
       Pragma_No_Run_Time,
       Pragma_No_Strict_Aliasing,
       Pragma_Normalize_Scalars,
+      Pragma_Optimize_Alignment,
       Pragma_Polling,
       Pragma_Persistent_BSS,
       Pragma_Priority_Specific_Dispatching,
@@ -1538,13 +1547,6 @@ package Snames is
       Task_Dispatching_FIFO_Within_Priorities);
    --  Id values used to identify task dispatching policies
 
-   ------------------
-   -- Helper types --
-   ------------------
-
-   type Attribute_Class_Array is array (Attribute_Id) of Boolean;
-   --  Type used to build attribute classification flag arrays
-
    -----------------
    -- Subprograms --
    -----------------
Index: snames.h
===================================================================
--- snames.h	(revision 133430)
+++ snames.h	(working copy)
@@ -111,79 +111,80 @@ extern unsigned char Get_Attribute_Id (i
 #define  Attr_Modulus                       64
 #define  Attr_Null_Parameter                65
 #define  Attr_Object_Size                   66
-#define  Attr_Partition_ID                  67
-#define  Attr_Passed_By_Reference           68
-#define  Attr_Pool_Address                  69
-#define  Attr_Pos                           70
-#define  Attr_Position                      71
-#define  Attr_Priority                      72
-#define  Attr_Range                         73
-#define  Attr_Range_Length                  74
-#define  Attr_Round                         75
-#define  Attr_Safe_Emax                     76
-#define  Attr_Safe_First                    77
-#define  Attr_Safe_Large                    78
-#define  Attr_Safe_Last                     79
-#define  Attr_Safe_Small                    80
-#define  Attr_Scale                         81
-#define  Attr_Scaling                       82
-#define  Attr_Signed_Zeros                  83
-#define  Attr_Size                          84
-#define  Attr_Small                         85
-#define  Attr_Storage_Size                  86
-#define  Attr_Storage_Unit                  87
-#define  Attr_Stream_Size                   88
-#define  Attr_Tag                           89
-#define  Attr_Target_Name                   90
-#define  Attr_Terminated                    91
-#define  Attr_To_Address                    92
-#define  Attr_Type_Class                    93
-#define  Attr_UET_Address                   94
-#define  Attr_Unbiased_Rounding             95
-#define  Attr_Unchecked_Access              96
-#define  Attr_Unconstrained_Array           97
-#define  Attr_Universal_Literal_String      98
-#define  Attr_Unrestricted_Access           99
-#define  Attr_VADS_Size                     100
-#define  Attr_Val                           101
-#define  Attr_Valid                         102
-#define  Attr_Value_Size                    103
-#define  Attr_Version                       104
-#define  Attr_Wchar_T_Size                  105
-#define  Attr_Wide_Wide_Width               106
-#define  Attr_Wide_Width                    107
-#define  Attr_Width                         108
-#define  Attr_Word_Size                     109
-#define  Attr_Adjacent                      110
-#define  Attr_Ceiling                       111
-#define  Attr_Copy_Sign                     112
-#define  Attr_Floor                         113
-#define  Attr_Fraction                      114
-#define  Attr_Image                         115
-#define  Attr_Input                         116
-#define  Attr_Machine                       117
-#define  Attr_Max                           118
-#define  Attr_Min                           119
-#define  Attr_Model                         120
-#define  Attr_Pred                          121
-#define  Attr_Remainder                     122
-#define  Attr_Rounding                      123
-#define  Attr_Succ                          124
-#define  Attr_Truncation                    125
-#define  Attr_Value                         126
-#define  Attr_Wide_Image                    127
-#define  Attr_Wide_Wide_Image               128
-#define  Attr_Wide_Value                    129
-#define  Attr_Wide_Wide_Value               130
-#define  Attr_Output                        131
-#define  Attr_Read                          132
-#define  Attr_Write                         133
-#define  Attr_Elab_Body                     134
-#define  Attr_Elab_Spec                     135
-#define  Attr_Storage_Pool                  136
-#define  Attr_Base                          137
-#define  Attr_Class                         138
-#define  Attr_Stub_Type                     139
+#define  Attr_Old                           67
+#define  Attr_Partition_ID                  68
+#define  Attr_Passed_By_Reference           69
+#define  Attr_Pool_Address                  70
+#define  Attr_Pos                           71
+#define  Attr_Position                      72
+#define  Attr_Priority                      73
+#define  Attr_Range                         74
+#define  Attr_Range_Length                  75
+#define  Attr_Round                         76
+#define  Attr_Safe_Emax                     77
+#define  Attr_Safe_First                    78
+#define  Attr_Safe_Large                    79
+#define  Attr_Safe_Last                     80
+#define  Attr_Safe_Small                    81
+#define  Attr_Scale                         82
+#define  Attr_Scaling                       83
+#define  Attr_Signed_Zeros                  84
+#define  Attr_Size                          85
+#define  Attr_Small                         86
+#define  Attr_Storage_Size                  87
+#define  Attr_Storage_Unit                  88
+#define  Attr_Stream_Size                   89
+#define  Attr_Tag                           90
+#define  Attr_Target_Name                   91
+#define  Attr_Terminated                    92
+#define  Attr_To_Address                    93
+#define  Attr_Type_Class                    94
+#define  Attr_UET_Address                   95
+#define  Attr_Unbiased_Rounding             96
+#define  Attr_Unchecked_Access              97
+#define  Attr_Unconstrained_Array           98
+#define  Attr_Universal_Literal_String      99
+#define  Attr_Unrestricted_Access           100
+#define  Attr_VADS_Size                     101
+#define  Attr_Val                           102
+#define  Attr_Valid                         103
+#define  Attr_Value_Size                    104
+#define  Attr_Version                       105
+#define  Attr_Wchar_T_Size                  106
+#define  Attr_Wide_Wide_Width               107
+#define  Attr_Wide_Width                    108
+#define  Attr_Width                         109
+#define  Attr_Word_Size                     110
+#define  Attr_Adjacent                      111
+#define  Attr_Ceiling                       112
+#define  Attr_Copy_Sign                     113
+#define  Attr_Floor                         114
+#define  Attr_Fraction                      115
+#define  Attr_Image                         116
+#define  Attr_Input                         117
+#define  Attr_Machine                       118
+#define  Attr_Max                           119
+#define  Attr_Min                           120
+#define  Attr_Model                         121
+#define  Attr_Pred                          122
+#define  Attr_Remainder                     123
+#define  Attr_Rounding                      124
+#define  Attr_Succ                          125
+#define  Attr_Truncation                    126
+#define  Attr_Value                         127
+#define  Attr_Wide_Image                    128
+#define  Attr_Wide_Wide_Image               129
+#define  Attr_Wide_Value                    130
+#define  Attr_Wide_Wide_Value               131
+#define  Attr_Output                        132
+#define  Attr_Read                          133
+#define  Attr_Write                         134
+#define  Attr_Elab_Body                     135
+#define  Attr_Elab_Spec                     136
+#define  Attr_Storage_Pool                  137
+#define  Attr_Base                          138
+#define  Attr_Class                         139
+#define  Attr_Stub_Type                     140
 
 /* Define the numeric values for the conventions.  */
 
@@ -247,138 +248,139 @@ extern unsigned char Get_Pragma_Id (int)
 #define  Pragma_No_Run_Time                   28
 #define  Pragma_No_Strict_Aliasing            29
 #define  Pragma_Normalize_Scalars             30
-#define  Pragma_Polling                       31
-#define  Pragma_Persistent_BSS                32
-#define  Pragma_Priority_Specific_Dispatching 33
-#define  Pragma_Profile                       34
-#define  Pragma_Profile_Warnings              35
-#define  Pragma_Propagate_Exceptions          36
-#define  Pragma_Queuing_Policy                37
-#define  Pragma_Ravenscar                     38
-#define  Pragma_Restricted_Run_Time           39
-#define  Pragma_Restrictions                  40
-#define  Pragma_Restriction_Warnings          41
-#define  Pragma_Reviewable                    42
-#define  Pragma_Source_File_Name              43
-#define  Pragma_Source_File_Name_Project      44
-#define  Pragma_Style_Checks                  45
-#define  Pragma_Suppress                      46
-#define  Pragma_Suppress_Exception_Locations  47
-#define  Pragma_Task_Dispatching_Policy       48
-#define  Pragma_Universal_Data                49
-#define  Pragma_Unsuppress                    50
-#define  Pragma_Use_VADS_Size                 51
-#define  Pragma_Validity_Checks               52
-#define  Pragma_Warnings                      53
-#define  Pragma_Wide_Character_Encoding       54
-#define  Pragma_Abort_Defer                   55
-#define  Pragma_All_Calls_Remote              56
-#define  Pragma_Annotate                      57
-#define  Pragma_Assert                        58
-#define  Pragma_Asynchronous                  59
-#define  Pragma_Atomic                        60
-#define  Pragma_Atomic_Components             61
-#define  Pragma_Attach_Handler                62
-#define  Pragma_CIL_Constructor               63
-#define  Pragma_Comment                       64
-#define  Pragma_Common_Object                 65
-#define  Pragma_Complete_Representation       66
-#define  Pragma_Complex_Representation        67
-#define  Pragma_Controlled                    68
-#define  Pragma_Convention                    69
-#define  Pragma_CPP_Class                     70
-#define  Pragma_CPP_Constructor               71
-#define  Pragma_CPP_Virtual                   72
-#define  Pragma_CPP_Vtable                    73
-#define  Pragma_Debug                         74
-#define  Pragma_Elaborate                     75
-#define  Pragma_Elaborate_All                 76
-#define  Pragma_Elaborate_Body                77
-#define  Pragma_Export                        78
-#define  Pragma_Export_Exception              79
-#define  Pragma_Export_Function               80
-#define  Pragma_Export_Object                 81
-#define  Pragma_Export_Procedure              82
-#define  Pragma_Export_Value                  83
-#define  Pragma_Export_Valued_Procedure       84
-#define  Pragma_External                      85
-#define  Pragma_Finalize_Storage_Only         86
-#define  Pragma_Ident                         87
-#define  Pragma_Implemented_By_Entry          88
-#define  Pragma_Import                        89
-#define  Pragma_Import_Exception              90
-#define  Pragma_Import_Function               91
-#define  Pragma_Import_Object                 92
-#define  Pragma_Import_Procedure              93
-#define  Pragma_Import_Valued_Procedure       94
-#define  Pragma_Inline                        95
-#define  Pragma_Inline_Always                 96
-#define  Pragma_Inline_Generic                97
-#define  Pragma_Inspection_Point              98
-#define  Pragma_Interface_Name                99
-#define  Pragma_Interrupt_Handler             100
-#define  Pragma_Interrupt_Priority            101
-#define  Pragma_Java_Constructor              102
-#define  Pragma_Java_Interface                103
-#define  Pragma_Keep_Names                    104
-#define  Pragma_Link_With                     105
-#define  Pragma_Linker_Alias                  106
-#define  Pragma_Linker_Constructor            107
-#define  Pragma_Linker_Destructor             108
-#define  Pragma_Linker_Options                109
-#define  Pragma_Linker_Section                110
-#define  Pragma_List                          111
-#define  Pragma_Machine_Attribute             112
-#define  Pragma_Main                          113
-#define  Pragma_Main_Storage                  114
-#define  Pragma_Memory_Size                   115
-#define  Pragma_No_Body                       116
-#define  Pragma_No_Return                     117
-#define  Pragma_Obsolescent                   118
-#define  Pragma_Optimize                      119
-#define  Pragma_Pack                          120
-#define  Pragma_Page                          121
-#define  Pragma_Passive                       122
-#define  Pragma_Preelaborable_Initialization  123
-#define  Pragma_Preelaborate                  124
-#define  Pragma_Preelaborate_05               125
-#define  Pragma_Psect_Object                  126
-#define  Pragma_Pure                          127
-#define  Pragma_Pure_05                       128
-#define  Pragma_Pure_Function                 129
-#define  Pragma_Remote_Call_Interface         130
-#define  Pragma_Remote_Types                  131
-#define  Pragma_Share_Generic                 132
-#define  Pragma_Shared                        133
-#define  Pragma_Shared_Passive                134
-#define  Pragma_Source_Reference              135
-#define  Pragma_Static_Elaboration_Desired    136
-#define  Pragma_Stream_Convert                137
-#define  Pragma_Subtitle                      138
-#define  Pragma_Suppress_All                  139
-#define  Pragma_Suppress_Debug_Info           140
-#define  Pragma_Suppress_Initialization       141
-#define  Pragma_System_Name                   142
-#define  Pragma_Task_Info                     143
-#define  Pragma_Task_Name                     144
-#define  Pragma_Task_Storage                  145
-#define  Pragma_Time_Slice                    146
-#define  Pragma_Title                         147
-#define  Pragma_Unchecked_Union               148
-#define  Pragma_Unimplemented_Unit            149
-#define  Pragma_Universal_Aliasing            150
-#define  Pragma_Unmodified                    151
-#define  Pragma_Unreferenced                  152
-#define  Pragma_Unreferenced_Objects          153
-#define  Pragma_Unreserve_All_Interrupts      154
-#define  Pragma_Volatile                      155
-#define  Pragma_Volatile_Components           156
-#define  Pragma_Weak_External                 157
-#define  Pragma_AST_Entry                     158
-#define  Pragma_Fast_Math                     159
-#define  Pragma_Interface                     160
-#define  Pragma_Priority                      161
-#define  Pragma_Storage_Size                  162
-#define  Pragma_Storage_Unit                  163
+#define  Pragma_Optimize_Alignment            31
+#define  Pragma_Polling                       32
+#define  Pragma_Persistent_BSS                33
+#define  Pragma_Priority_Specific_Dispatching 34
+#define  Pragma_Profile                       35
+#define  Pragma_Profile_Warnings              36
+#define  Pragma_Propagate_Exceptions          37
+#define  Pragma_Queuing_Policy                38
+#define  Pragma_Ravenscar                     39
+#define  Pragma_Restricted_Run_Time           40
+#define  Pragma_Restrictions                  41
+#define  Pragma_Restriction_Warnings          42
+#define  Pragma_Reviewable                    43
+#define  Pragma_Source_File_Name              44
+#define  Pragma_Source_File_Name_Project      45
+#define  Pragma_Style_Checks                  46
+#define  Pragma_Suppress                      47
+#define  Pragma_Suppress_Exception_Locations  48
+#define  Pragma_Task_Dispatching_Policy       49
+#define  Pragma_Universal_Data                50
+#define  Pragma_Unsuppress                    51
+#define  Pragma_Use_VADS_Size                 52
+#define  Pragma_Validity_Checks               53
+#define  Pragma_Warnings                      54
+#define  Pragma_Wide_Character_Encoding       55
+#define  Pragma_Abort_Defer                   56
+#define  Pragma_All_Calls_Remote              57
+#define  Pragma_Annotate                      58
+#define  Pragma_Assert                        59
+#define  Pragma_Asynchronous                  60
+#define  Pragma_Atomic                        61
+#define  Pragma_Atomic_Components             62
+#define  Pragma_Attach_Handler                63
+#define  Pragma_CIL_Constructor               64
+#define  Pragma_Comment                       65
+#define  Pragma_Common_Object                 66
+#define  Pragma_Complete_Representation       67
+#define  Pragma_Complex_Representation        68
+#define  Pragma_Controlled                    69
+#define  Pragma_Convention                    70
+#define  Pragma_CPP_Class                     71
+#define  Pragma_CPP_Constructor               72
+#define  Pragma_CPP_Virtual                   73
+#define  Pragma_CPP_Vtable                    74
+#define  Pragma_Debug                         75
+#define  Pragma_Elaborate                     76
+#define  Pragma_Elaborate_All                 77
+#define  Pragma_Elaborate_Body                78
+#define  Pragma_Export                        79
+#define  Pragma_Export_Exception              80
+#define  Pragma_Export_Function               81
+#define  Pragma_Export_Object                 82
+#define  Pragma_Export_Procedure              83
+#define  Pragma_Export_Value                  84
+#define  Pragma_Export_Valued_Procedure       85
+#define  Pragma_External                      86
+#define  Pragma_Finalize_Storage_Only         87
+#define  Pragma_Ident                         88
+#define  Pragma_Implemented_By_Entry          89
+#define  Pragma_Import                        90
+#define  Pragma_Import_Exception              91
+#define  Pragma_Import_Function               92
+#define  Pragma_Import_Object                 93
+#define  Pragma_Import_Procedure              94
+#define  Pragma_Import_Valued_Procedure       95
+#define  Pragma_Inline                        96
+#define  Pragma_Inline_Always                 97
+#define  Pragma_Inline_Generic                98
+#define  Pragma_Inspection_Point              99
+#define  Pragma_Interface_Name                100
+#define  Pragma_Interrupt_Handler             101
+#define  Pragma_Interrupt_Priority            102
+#define  Pragma_Java_Constructor              103
+#define  Pragma_Java_Interface                104
+#define  Pragma_Keep_Names                    105
+#define  Pragma_Link_With                     106
+#define  Pragma_Linker_Alias                  107
+#define  Pragma_Linker_Constructor            108
+#define  Pragma_Linker_Destructor             109
+#define  Pragma_Linker_Options                110
+#define  Pragma_Linker_Section                111
+#define  Pragma_List                          112
+#define  Pragma_Machine_Attribute             113
+#define  Pragma_Main                          114
+#define  Pragma_Main_Storage                  115
+#define  Pragma_Memory_Size                   116
+#define  Pragma_No_Body                       117
+#define  Pragma_No_Return                     118
+#define  Pragma_Obsolescent                   119
+#define  Pragma_Optimize                      120
+#define  Pragma_Pack                          121
+#define  Pragma_Page                          122
+#define  Pragma_Passive                       123
+#define  Pragma_Preelaborable_Initialization  124
+#define  Pragma_Preelaborate                  125
+#define  Pragma_Preelaborate_05               126
+#define  Pragma_Psect_Object                  127
+#define  Pragma_Pure                          128
+#define  Pragma_Pure_05                       129
+#define  Pragma_Pure_Function                 130
+#define  Pragma_Remote_Call_Interface         131
+#define  Pragma_Remote_Types                  132
+#define  Pragma_Share_Generic                 133
+#define  Pragma_Shared                        134
+#define  Pragma_Shared_Passive                135
+#define  Pragma_Source_Reference              136
+#define  Pragma_Static_Elaboration_Desired    137
+#define  Pragma_Stream_Convert                138
+#define  Pragma_Subtitle                      139
+#define  Pragma_Suppress_All                  140
+#define  Pragma_Suppress_Debug_Info           141
+#define  Pragma_Suppress_Initialization       142
+#define  Pragma_System_Name                   143
+#define  Pragma_Task_Info                     144
+#define  Pragma_Task_Name                     145
+#define  Pragma_Task_Storage                  146
+#define  Pragma_Time_Slice                    147
+#define  Pragma_Title                         148
+#define  Pragma_Unchecked_Union               149
+#define  Pragma_Unimplemented_Unit            150
+#define  Pragma_Universal_Aliasing            151
+#define  Pragma_Unmodified                    152
+#define  Pragma_Unreferenced                  153
+#define  Pragma_Unreferenced_Objects          154
+#define  Pragma_Unreserve_All_Interrupts      155
+#define  Pragma_Volatile                      156
+#define  Pragma_Volatile_Components           157
+#define  Pragma_Weak_External                 158
+#define  Pragma_AST_Entry                     159
+#define  Pragma_Fast_Math                     160
+#define  Pragma_Interface                     161
+#define  Pragma_Priority                      162
+#define  Pragma_Storage_Size                  163
+#define  Pragma_Storage_Unit                  164
 
 /* End of snames.h (C version of Snames package spec) */
Index: snames.adb
===================================================================
--- snames.adb	(revision 133430)
+++ snames.adb	(working copy)
@@ -206,6 +206,7 @@ package body Snames is
      "no_run_time#" &
      "no_strict_aliasing#" &
      "normalize_scalars#" &
+     "optimize_alignment#" &
      "polling#" &
      "persistent_bss#" &
      "priority_specific_dispatching#" &
@@ -495,6 +496,7 @@ package body Snames is
      "modulus#" &
      "null_parameter#" &
      "object_size#" &
+     "old#" &
      "partition_id#" &
      "passed_by_reference#" &
      "pool_address#" &
@@ -778,6 +780,8 @@ package body Snames is
      "stack#" &
      "switches#" &
      "symbolic_link_supported#" &
+     "sync#" &
+     "synchronize#" &
      "toolchain_description#" &
      "toolchain_version#" &
      "runtime_library_dir#" &


More information about the Gcc-patches mailing list