OSDN Git Service

2008-05-27 Vincent Celier <celier@adacore.com>
[pf3gnuchains/gcc-fork.git] / gcc / ada / sem_ch9.adb
index 2075e5e..8a85b11 100644 (file)
@@ -6,23 +6,20 @@
 --                                                                          --
 --                                 B o d y                                  --
 --                                                                          --
---                            $Revision: 1.235 $
---                                                                          --
---          Copyright (C) 1992-2001, 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- --
--- ware  Foundation;  either version 2,  or (at your option) any later ver- --
+-- ware  Foundation;  either version 3,  or (at your option) any later ver- --
 -- sion.  GNAT is distributed in the hope that it will be useful, but WITH- --
 -- OUT ANY WARRANTY;  without even the  implied warranty of MERCHANTABILITY --
 -- or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License --
 -- for  more details.  You should have  received  a copy of the GNU General --
--- Public License  distributed with GNAT;  see file COPYING.  If not, write --
--- to  the Free Software Foundation,  59 Temple Place - Suite 330,  Boston, --
--- MA 02111-1307, USA.                                                      --
+-- Public License  distributed with GNAT; see file COPYING3.  If not, go to --
+-- http://www.gnu.org/licenses for a complete copy of the license.          --
 --                                                                          --
 -- GNAT was originally developed  by the GNAT team at  New York University. --
--- It is now maintained by Ada Core Technologies Inc (http://www.gnat.com). --
+-- Extensive contributions were provided by Ada Core Technologies Inc.      --
 --                                                                          --
 ------------------------------------------------------------------------------
 
@@ -30,14 +27,17 @@ with Atree;    use Atree;
 with Checks;   use Checks;
 with Einfo;    use Einfo;
 with Errout;   use Errout;
-with Exp_Ch9;
+with Exp_Ch9;  use Exp_Ch9;
 with Elists;   use Elists;
+with Freeze;   use Freeze;
 with Itypes;   use Itypes;
 with Lib.Xref; use Lib.Xref;
+with Namet;    use Namet;
 with Nlists;   use Nlists;
 with Nmake;    use Nmake;
 with Opt;      use Opt;
 with Restrict; use Restrict;
+with Rident;   use Rident;
 with Rtsfind;  use Rtsfind;
 with Sem;      use Sem;
 with Sem_Ch3;  use Sem_Ch3;
@@ -53,6 +53,7 @@ with Snames;   use Snames;
 with Stand;    use Stand;
 with Sinfo;    use Sinfo;
 with Style;
+with Targparm; use Targparm;
 with Tbuild;   use Tbuild;
 with Uintp;    use Uintp;
 
@@ -62,19 +63,32 @@ package body Sem_Ch9 is
    -- Local Subprograms --
    -----------------------
 
-   procedure Check_Max_Entries (Def : Node_Id; R : Restriction_Parameter_Id);
-   --  Given either a protected definition or a task definition in Def, check
+   procedure Check_Max_Entries (D : Node_Id; R : All_Parameter_Restrictions);
+   --  Given either a protected definition or a task definition in D, check
    --  the corresponding restriction parameter identifier R, and if it is set,
    --  count the entries (checking the static requirement), and compare with
    --  the given maximum.
 
+   procedure Check_Interfaces (N : Node_Id; T : Entity_Id);
+   --  N is an N_Protected_Type_Declaration or N_Task_Type_Declaration node.
+   --  Complete decoration of T and check legality of the covered interfaces.
+
+   procedure Check_Triggering_Statement
+     (Trigger        : Node_Id;
+      Error_Node     : Node_Id;
+      Is_Dispatching : out Boolean);
+   --  Examine the triggering statement of a select statement, conditional or
+   --  timed entry call. If Trigger is a dispatching call, return its status
+   --  in Is_Dispatching and check whether the primitive belongs to a limited
+   --  interface. If it does not, emit an error at Error_Node.
+
    function Find_Concurrent_Spec (Body_Id : Entity_Id) return Entity_Id;
    --  Find entity in corresponding task or protected declaration. Use full
    --  view if first declaration was for an incomplete type.
 
    procedure Install_Declarations (Spec : Entity_Id);
-   --  Utility to make visible in corresponding body the entities defined
-   --  in task, protected type declaration, or entry declaration.
+   --  Utility to make visible in corresponding body the entities defined in
+   --  task, protected type declaration, or entry declaration.
 
    -----------------------------
    -- Analyze_Abort_Statement --
@@ -89,11 +103,22 @@ package body Sem_Ch9 is
       while Present (T_Name) loop
          Analyze (T_Name);
 
-         if not Is_Task_Type (Etype (T_Name)) then
-            Error_Msg_N ("expect task name for ABORT", T_Name);
-            return;
+         if Is_Task_Type (Etype (T_Name))
+           or else (Ada_Version >= Ada_05
+                      and then Ekind (Etype (T_Name)) = E_Class_Wide_Type
+                      and then Is_Interface (Etype (T_Name))
+                      and then Is_Task_Interface (Etype (T_Name)))
+         then
+            Resolve (T_Name);
          else
-            Resolve (T_Name,  Etype (T_Name));
+            if Ada_Version >= Ada_05 then
+               Error_Msg_N ("expect task name or task interface class-wide "
+                          & "object for ABORT", T_Name);
+            else
+               Error_Msg_N ("expect task name for ABORT", T_Name);
+            end if;
+
+            return;
          end if;
 
          Next (T_Name);
@@ -115,12 +140,12 @@ package body Sem_Ch9 is
          Analyze_List (Pragmas_Before (N));
       end if;
 
-      Analyze (Accept_Statement (N));
-
       if Present (Condition (N)) then
          Analyze_And_Resolve (Condition (N), Any_Boolean);
       end if;
 
+      Analyze (Accept_Statement (N));
+
       if Is_Non_Empty_List (Statements (N)) then
          Analyze_Statements (Statements (N));
       end if;
@@ -135,7 +160,7 @@ package body Sem_Ch9 is
       Formals   : constant List_Id   := Parameter_Specifications (N);
       Index     : constant Node_Id   := Entry_Index (N);
       Stats     : constant Node_Id   := Handled_Statement_Sequence (N);
-      Ityp      : Entity_Id;
+      Accept_Id : Entity_Id;
       Entry_Nam : Entity_Id;
       E         : Entity_Id;
       Kind      : Entity_Kind;
@@ -146,30 +171,36 @@ package body Sem_Ch9 is
       -----------------------
 
       function Actual_Index_Type (E : Entity_Id) return Entity_Id;
-      --  If the bounds of an entry family depend on task discriminants,
-      --  create a new index type where a discriminant is replaced by the
-      --  local variable that renames it in the task body.
+      --  If the bounds of an entry family depend on task discriminants, create
+      --  a new index type where a discriminant is replaced by the local
+      --  variable that renames it in the task body.
+
+      -----------------------
+      -- Actual_Index_Type --
+      -----------------------
 
       function Actual_Index_Type (E : Entity_Id) return Entity_Id is
-         Typ   : Entity_Id := Entry_Index_Type (E);
-         Lo    : Node_Id := Type_Low_Bound  (Typ);
-         Hi    : Node_Id := Type_High_Bound (Typ);
+         Typ   : constant Entity_Id := Entry_Index_Type (E);
+         Lo    : constant Node_Id   := Type_Low_Bound  (Typ);
+         Hi    : constant Node_Id   := Type_High_Bound (Typ);
          New_T : Entity_Id;
 
          function Actual_Discriminant_Ref (Bound : Node_Id) return Node_Id;
          --  If bound is discriminant reference, replace with corresponding
          --  local variable of the same name.
 
+         -----------------------------
+         -- Actual_Discriminant_Ref --
+         -----------------------------
+
          function Actual_Discriminant_Ref (Bound : Node_Id) return Node_Id is
-            Typ : Entity_Id := Etype (Bound);
+            Typ : constant Entity_Id := Etype (Bound);
             Ref : Node_Id;
-
          begin
             if not Is_Entity_Name (Bound)
               or else Ekind (Entity (Bound)) /= E_Discriminant
             then
                return Bound;
-
             else
                Ref := Make_Identifier (Sloc (N), Chars (Entity (Bound)));
                Analyze (Ref);
@@ -230,38 +261,39 @@ package body Sem_Ch9 is
 
       --  In order to process the parameters, we create a defining
       --  identifier that can be used as the name of the scope. The
-      --  name of the accept statement itself is not a defining identifier.
+      --  name of the accept statement itself is not a defining identifier,
+      --  and we cannot use its name directly because the task may have
+      --  any number of accept statements for the same entry.
 
       if Present (Index) then
-         Ityp := New_Internal_Entity
+         Accept_Id := New_Internal_Entity
            (E_Entry_Family, Current_Scope, Sloc (N), 'E');
       else
-         Ityp := New_Internal_Entity
+         Accept_Id := New_Internal_Entity
            (E_Entry, Current_Scope, Sloc (N), 'E');
       end if;
 
-      Set_Etype          (Ityp, Standard_Void_Type);
-      Set_Accept_Address (Ityp, New_Elmt_List);
+      Set_Etype          (Accept_Id, Standard_Void_Type);
+      Set_Accept_Address (Accept_Id, New_Elmt_List);
 
       if Present (Formals) then
-         New_Scope (Ityp);
-         Process_Formals (Ityp, Formals, N);
-         Create_Extra_Formals (Ityp);
+         Push_Scope (Accept_Id);
+         Process_Formals (Formals, N);
+         Create_Extra_Formals (Accept_Id);
          End_Scope;
       end if;
 
-      --  We set the default expressions processed flag because we don't
-      --  need default expression functions. This is really more like a
-      --  body entity than a spec entity anyway.
+      --  We set the default expressions processed flag because we don't need
+      --  default expression functions. This is really more like body entity
+      --  than a spec entity anyway.
 
-      Set_Default_Expressions_Processed (Ityp);
+      Set_Default_Expressions_Processed (Accept_Id);
 
       E := First_Entity (Etype (Task_Nam));
-
       while Present (E) loop
          if Chars (E) = Chars (Nam)
-           and then (Ekind (E) = Ekind (Ityp))
-           and then Type_Conformant (Ityp, E)
+           and then (Ekind (E) = Ekind (Accept_Id))
+           and then Type_Conformant (Accept_Id, E)
          then
             Entry_Nam := E;
             exit;
@@ -275,12 +307,12 @@ package body Sem_Ch9 is
          return;
       else
          Set_Entity (Nam, Entry_Nam);
-         Generate_Reference (Entry_Nam, Nam, 'b');
+         Generate_Reference (Entry_Nam, Nam, 'b', Set_Ref => False);
          Style.Check_Identifier (Nam, Entry_Nam);
       end if;
 
-      --  Verify that the entry is not hidden by a procedure declared in
-      --  the current block (pathological but possible).
+      --  Verify that the entry is not hidden by a procedure declared in the
+      --  current block (pathological but possible).
 
       if Current_Scope /= Task_Nam then
          declare
@@ -288,10 +320,9 @@ package body Sem_Ch9 is
 
          begin
             E1 := First_Entity (Current_Scope);
-
             while Present (E1) loop
-
                if Ekind (E1) = E_Procedure
+                 and then Chars (E1) = Chars (Entry_Nam)
                  and then Type_Conformant (E1, Entry_Nam)
                then
                   Error_Msg_N ("entry name is not visible", N);
@@ -302,8 +333,8 @@ package body Sem_Ch9 is
          end;
       end if;
 
-      Set_Convention (Ityp, Convention (Entry_Nam));
-      Check_Fully_Conformant (Ityp, Entry_Nam, N);
+      Set_Convention (Accept_Id, Convention (Entry_Nam));
+      Check_Fully_Conformant (Accept_Id, Entry_Nam, N);
 
       for J in reverse 0 .. Scope_Stack.Last loop
          exit when Task_Nam = Scope_Stack.Table (J).Entity;
@@ -345,30 +376,17 @@ package body Sem_Ch9 is
          Error_Msg_N ("invalid entry index in accept for simple entry", N);
       end if;
 
-      --  If statements are present, they must be analyzed in the context
-      --  of the entry, so that references to formals are correctly resolved.
-      --  We also have to add the declarations that are required by the
-      --  expansion of the accept statement in this case if expansion active.
-
-      --  In the case of a select alternative of a selective accept,
-      --  the expander references the address declaration even if there
-      --  is no statement list.
-
-      Exp_Ch9.Expand_Accept_Declarations (N, Entry_Nam);
-
-      --  If label declarations present, analyze them. They are declared
-      --  in the enclosing task, but their enclosing scope is the entry itself,
-      --  so that goto's to the label are recognized as local to the accept.
+      --  If label declarations present, analyze them. They are declared in the
+      --  enclosing task, but their enclosing scope is the entry itself, so
+      --  that goto's to the label are recognized as local to the accept.
 
       if Present (Declarations (N)) then
-
          declare
             Decl : Node_Id;
             Id   : Entity_Id;
 
          begin
             Decl := First (Declarations (N));
-
             while Present (Decl) loop
                Analyze (Decl);
 
@@ -382,24 +400,52 @@ package body Sem_Ch9 is
          end;
       end if;
 
-      --  Set Not_Source_Assigned flag on all entry formals
+      --  If statements are present, they must be analyzed in the context of
+      --  the entry, so that references to formals are correctly resolved. We
+      --  also have to add the declarations that are required by the expansion
+      --  of the accept statement in this case if expansion active.
 
-      E := First_Entity (Entry_Nam);
+      --  In the case of a select alternative of a selective accept, the
+      --  expander references the address declaration even if there is no
+      --  statement list.
 
+      --  We also need to create the renaming declarations for the local
+      --  variables that will replace references to the formals within the
+      --  accept statement.
+
+      Exp_Ch9.Expand_Accept_Declarations (N, Entry_Nam);
+
+      --  Set Never_Set_In_Source and clear Is_True_Constant/Current_Value
+      --  fields on all entry formals (this loop ignores all other entities).
+      --  Reset Referenced, Referenced_As_xxx and Has_Pragma_Unreferenced as
+      --  well, so that we can post accurate warnings on each accept statement
+      --  for the same entry.
+
+      E := First_Entity (Entry_Nam);
       while Present (E) loop
-         Set_Not_Source_Assigned (E, True);
+         if Is_Formal (E) then
+            Set_Never_Set_In_Source         (E, True);
+            Set_Is_True_Constant            (E, False);
+            Set_Current_Value               (E, Empty);
+            Set_Referenced                  (E, False);
+            Set_Referenced_As_LHS           (E, False);
+            Set_Referenced_As_Out_Parameter (E, False);
+            Set_Has_Pragma_Unreferenced     (E, False);
+         end if;
+
          Next_Entity (E);
       end loop;
 
       --  Analyze statements if present
 
       if Present (Stats) then
-         New_Scope (Entry_Nam);
+         Push_Scope (Entry_Nam);
          Install_Declarations (Entry_Nam);
 
          Set_Actual_Subtypes (N, Current_Scope);
+
          Analyze (Stats);
-         Process_End_Label (Handled_Statement_Sequence (N), 't');
+         Process_End_Label (Handled_Statement_Sequence (N), 't', Entry_Nam);
          End_Scope;
       end if;
 
@@ -408,7 +454,6 @@ package body Sem_Ch9 is
       Check_Potentially_Blocking_Operation (N);
       Check_References (Entry_Nam, N);
       Set_Entry_Accepted (Entry_Nam);
-
    end Analyze_Accept_Statement;
 
    ---------------------------------
@@ -416,14 +461,43 @@ package body Sem_Ch9 is
    ---------------------------------
 
    procedure Analyze_Asynchronous_Select (N : Node_Id) is
+      Is_Disp_Select : Boolean := False;
+      Trigger        : Node_Id;
+
    begin
       Tasking_Used := True;
       Check_Restriction (Max_Asynchronous_Select_Nesting, N);
       Check_Restriction (No_Select_Statements, N);
 
-      Analyze (Triggering_Alternative (N));
+      if Ada_Version >= Ada_05 then
+         Trigger := Triggering_Statement (Triggering_Alternative (N));
+
+         Analyze (Trigger);
+
+         --  Ada 2005 (AI-345): Check for a potential dispatching select
+
+         Check_Triggering_Statement (Trigger, N, Is_Disp_Select);
+      end if;
+
+      --  Ada 2005 (AI-345): The expansion of the dispatching asynchronous
+      --  select will have to duplicate the triggering statements. Postpone
+      --  the analysis of the statements till expansion. Analyze only if the
+      --  expander is disabled in order to catch any semantic errors.
+
+      if Is_Disp_Select then
+         if not Expander_Active then
+            Analyze_Statements (Statements (Abortable_Part (N)));
+            Analyze (Triggering_Alternative (N));
+         end if;
 
-      Analyze_Statements (Statements (Abortable_Part (N)));
+      --  Analyze the statements. We analyze statements in the abortable part,
+      --  because this is the section that is executed first, and that way our
+      --  remembering of saved values and checks is accurate.
+
+      else
+         Analyze_Statements (Statements (Abortable_Part (N)));
+         Analyze (Triggering_Alternative (N));
+      end if;
    end Analyze_Asynchronous_Select;
 
    ------------------------------------
@@ -431,11 +505,45 @@ package body Sem_Ch9 is
    ------------------------------------
 
    procedure Analyze_Conditional_Entry_Call (N : Node_Id) is
+      Trigger        : constant Node_Id :=
+                         Entry_Call_Statement (Entry_Call_Alternative (N));
+      Is_Disp_Select : Boolean := False;
+
    begin
       Check_Restriction (No_Select_Statements, N);
       Tasking_Used := True;
-      Analyze (Entry_Call_Alternative (N));
-      Analyze_Statements (Else_Statements (N));
+
+      --  Ada 2005 (AI-345): The trigger may be a dispatching call
+
+      if Ada_Version >= Ada_05 then
+         Analyze (Trigger);
+         Check_Triggering_Statement (Trigger, N, Is_Disp_Select);
+      end if;
+
+      if List_Length (Else_Statements (N)) = 1
+        and then Nkind (First (Else_Statements (N))) in N_Delay_Statement
+      then
+         Error_Msg_N
+           ("suspicious form of conditional entry call?!", N);
+         Error_Msg_N
+           ("\`SELECT OR` may be intended rather than `SELECT ELSE`!", N);
+      end if;
+
+      --  Postpone the analysis of the statements till expansion. Analyze only
+      --  if the expander is disabled in order to catch any semantic errors.
+
+      if Is_Disp_Select then
+         if not Expander_Active then
+            Analyze (Entry_Call_Alternative (N));
+            Analyze_Statements (Else_Statements (N));
+         end if;
+
+      --  Regular select analysis
+
+      else
+         Analyze (Entry_Call_Alternative (N));
+         Analyze_Statements (Else_Statements (N));
+      end if;
    end Analyze_Conditional_Entry_Call;
 
    --------------------------------
@@ -444,6 +552,7 @@ package body Sem_Ch9 is
 
    procedure Analyze_Delay_Alternative (N : Node_Id) is
       Expr : Node_Id;
+      Typ  : Entity_Id;
 
    begin
       Tasking_Used := True;
@@ -453,23 +562,30 @@ package body Sem_Ch9 is
          Analyze_List (Pragmas_Before (N));
       end if;
 
-      if Nkind (Parent (N)) = N_Selective_Accept
-        or else Nkind (Parent (N)) = N_Timed_Entry_Call
-      then
+      if Nkind_In (Parent (N), N_Selective_Accept, N_Timed_Entry_Call) then
          Expr := Expression (Delay_Statement (N));
 
-         --  defer full analysis until the statement is expanded, to insure
+         --  Defer full analysis until the statement is expanded, to insure
          --  that generated code does not move past the guard. The delay
          --  expression is only evaluated if the guard is open.
 
          if Nkind (Delay_Statement (N)) = N_Delay_Relative_Statement then
-            Pre_Analyze_And_Resolve (Expr, Standard_Duration);
-
+            Preanalyze_And_Resolve (Expr, Standard_Duration);
          else
-            Pre_Analyze_And_Resolve (Expr);
+            Preanalyze_And_Resolve (Expr);
+         end if;
+
+         Typ := First_Subtype (Etype (Expr));
+
+         if Nkind (Delay_Statement (N)) = N_Delay_Until_Statement
+           and then not Is_RTE (Typ, RO_CA_Time)
+           and then not Is_RTE (Typ, RO_RT_Time)
+         then
+            Error_Msg_N ("expect Time types for `DELAY UNTIL`", Expr);
          end if;
 
          Check_Restriction (No_Fixed_Point, Expr);
+
       else
          Analyze (Delay_Statement (N));
       end if;
@@ -489,7 +605,6 @@ package body Sem_Ch9 is
 
    procedure Analyze_Delay_Relative (N : Node_Id) is
       E : constant Node_Id := Expression (N);
-
    begin
       Check_Restriction (No_Relative_Delay, N);
       Tasking_Used := True;
@@ -504,16 +619,18 @@ package body Sem_Ch9 is
    -------------------------
 
    procedure Analyze_Delay_Until (N : Node_Id) is
-      E : constant Node_Id := Expression (N);
+      E   : constant Node_Id := Expression (N);
+      Typ : Entity_Id;
 
    begin
       Tasking_Used := True;
       Check_Restriction (No_Delay, N);
       Check_Potentially_Blocking_Operation (N);
       Analyze (E);
+      Typ := First_Subtype (Etype (E));
 
-      if not Is_RTE (Base_Type (Etype (E)), RO_CA_Time) and then
-         not Is_RTE (Base_Type (Etype (E)), RO_RT_Time)
+      if not Is_RTE (Typ, RO_CA_Time) and then
+         not Is_RTE (Typ, RO_RT_Time)
       then
          Error_Msg_N ("expect Time types for `DELAY UNTIL`", E);
       end if;
@@ -529,8 +646,8 @@ package body Sem_Ch9 is
       Stats      : constant Node_Id   := Handled_Statement_Sequence (N);
       Formals    : constant Node_Id   := Entry_Body_Formal_Part (N);
       P_Type     : constant Entity_Id := Current_Scope;
-      Entry_Name : Entity_Id;
       E          : Entity_Id;
+      Entry_Name : Entity_Id;
 
    begin
       Tasking_Used := True;
@@ -560,7 +677,71 @@ package body Sem_Ch9 is
          then
             Entry_Name := E;
             Set_Convention (Id, Convention (E));
+            Set_Corresponding_Body (Parent (Entry_Name), Id);
             Check_Fully_Conformant (Id, E, N);
+
+            if Ekind (Id) = E_Entry_Family then
+               if not Fully_Conformant_Discrete_Subtypes (
+                  Discrete_Subtype_Definition (Parent (E)),
+                  Discrete_Subtype_Definition
+                    (Entry_Index_Specification (Formals)))
+               then
+                  Error_Msg_N
+                    ("index not fully conformant with previous declaration",
+                      Discrete_Subtype_Definition
+                       (Entry_Index_Specification (Formals)));
+
+               else
+                  --  The elaboration of the entry body does not recompute the
+                  --  bounds of the index, which may have side effects. Inherit
+                  --  the bounds from the entry declaration. This is critical
+                  --  if the entry has a per-object constraint. If a bound is
+                  --  given by a discriminant, it must be reanalyzed in order
+                  --  to capture the discriminal of the current entry, rather
+                  --  than that of the protected type.
+
+                  declare
+                     Index_Spec : constant Node_Id :=
+                                    Entry_Index_Specification (Formals);
+
+                     Def : constant Node_Id :=
+                             New_Copy_Tree
+                               (Discrete_Subtype_Definition (Parent (E)));
+
+                  begin
+                     if Nkind
+                       (Original_Node
+                         (Discrete_Subtype_Definition (Index_Spec))) = N_Range
+                     then
+                        Set_Etype (Def, Empty);
+                        Set_Analyzed (Def, False);
+
+                        --  Keep the original subtree to ensure a properly
+                        --  formed tree (e.g. for ASIS use).
+
+                        Rewrite
+                          (Discrete_Subtype_Definition (Index_Spec), Def);
+
+                        Set_Analyzed (Low_Bound (Def), False);
+                        Set_Analyzed (High_Bound (Def), False);
+
+                        if Denotes_Discriminant (Low_Bound (Def)) then
+                           Set_Entity (Low_Bound (Def), Empty);
+                        end if;
+
+                        if Denotes_Discriminant (High_Bound (Def)) then
+                           Set_Entity (High_Bound (Def), Empty);
+                        end if;
+
+                        Analyze (Def);
+                        Make_Index (Def, Index_Spec);
+                        Set_Etype
+                          (Defining_Identifier (Index_Spec), Etype (Def));
+                     end if;
+                  end;
+               end if;
+            end if;
+
             exit;
          end if;
 
@@ -577,37 +758,108 @@ package body Sem_Ch9 is
 
       else
          Set_Has_Completion (Entry_Name);
-         Generate_Reference (Entry_Name, Id, 'b');
+         Generate_Reference (Entry_Name, Id, 'b', Set_Ref => False);
          Style.Check_Identifier (Id, Entry_Name);
       end if;
 
       Exp_Ch9.Expand_Entry_Barrier (N, Entry_Name);
-      New_Scope (Entry_Name);
+      Push_Scope (Entry_Name);
 
-      Exp_Ch9.Expand_Entry_Body_Declarations (N);
       Install_Declarations (Entry_Name);
       Set_Actual_Subtypes (N, Current_Scope);
 
       --  The entity for the protected subprogram corresponding to the entry
       --  has been created. We retain the name of this entity in the entry
       --  body, for use when the corresponding subprogram body is created.
-      --  Note that entry bodies have to corresponding_spec, and there is no
+      --  Note that entry bodies have no corresponding_spec, and there is no
       --  easy link back in the tree between the entry body and the entity for
-      --  the entry itself.
+      --  the entry itself, which is why we must propagate some attributes
+      --  explicitly from spec to body.
+
+      Set_Protected_Body_Subprogram
+        (Id, Protected_Body_Subprogram (Entry_Name));
+
+      Set_Entry_Parameters_Type
+        (Id, Entry_Parameters_Type (Entry_Name));
+
+      --  Add a declaration for the Protection object, renaming declarations
+      --  for the discriminals and privals and finally a declaration for the
+      --  entry family index (if applicable).
 
-      Set_Protected_Body_Subprogram (Id,
-        Protected_Body_Subprogram (Entry_Name));
+      if Expander_Active
+        and then Is_Protected_Type (P_Type)
+      then
+         Install_Private_Data_Declarations
+           (Sloc (N), Entry_Name, P_Type, N, Decls);
+      end if;
 
       if Present (Decls) then
          Analyze_Declarations (Decls);
+         Inspect_Deferred_Constant_Completion (Decls);
       end if;
 
       if Present (Stats) then
          Analyze (Stats);
       end if;
 
+      --  Check for unreferenced variables etc. Before the Check_References
+      --  call, we transfer Never_Set_In_Source and Referenced flags from
+      --  parameters in the spec to the corresponding entities in the body,
+      --  since we want the warnings on the body entities. Note that we do
+      --  not have to transfer Referenced_As_LHS, since that flag can only
+      --  be set for simple variables.
+
+      --  At the same time, we set the flags on the spec entities to suppress
+      --  any warnings on the spec formals, since we also scan the spec.
+      --  Finally, we propagate the Entry_Component attribute to the body
+      --  formals, for use in the renaming declarations created later for the
+      --  formals (see exp_ch9.Add_Formal_Renamings).
+
+      declare
+         E1 : Entity_Id;
+         E2 : Entity_Id;
+
+      begin
+         E1 := First_Entity (Entry_Name);
+         while Present (E1) loop
+            E2 := First_Entity (Id);
+            while Present (E2) loop
+               exit when Chars (E1) = Chars (E2);
+               Next_Entity (E2);
+            end loop;
+
+            --  If no matching body entity, then we already had a detected
+            --  error of some kind, so just don't worry about these warnings.
+
+            if No (E2) then
+               goto Continue;
+            end if;
+
+            if Ekind (E1) = E_Out_Parameter then
+               Set_Never_Set_In_Source (E2, Never_Set_In_Source (E1));
+               Set_Never_Set_In_Source (E1, False);
+            end if;
+
+            Set_Referenced (E2, Referenced (E1));
+            Set_Referenced (E1);
+            Set_Entry_Component (E2, Entry_Component (E1));
+
+         <<Continue>>
+            Next_Entity (E1);
+         end loop;
+
+         Check_References (Id);
+      end;
+
+      --  We still need to check references for the spec, since objects
+      --  declared in the body are chained (in the First_Entity sense) to
+      --  the spec rather than the body in the case of entries.
+
       Check_References (Entry_Name);
-      Process_End_Label (Handled_Statement_Sequence (N), 't');
+
+      --  Process the end label, and terminate the scope
+
+      Process_End_Label (Handled_Statement_Sequence (N), 't', Entry_Name);
       End_Scope;
 
       --  If this is an entry family, remove the loop created to provide
@@ -618,7 +870,6 @@ package body Sem_Ch9 is
       then
          End_Scope;
       end if;
-
    end Analyze_Entry_Body;
 
    ------------------------------------
@@ -635,15 +886,19 @@ package body Sem_Ch9 is
 
       if Present (Index) then
          Analyze (Index);
+
+         --  The entry index functions like a loop variable, thus it is known
+         --  to have a valid value.
+
+         Set_Is_Known_Valid (Defining_Identifier (Index));
       end if;
 
       if Present (Formals) then
          Set_Scope (Id, Current_Scope);
-         New_Scope (Id);
-         Process_Formals (Id, Formals, Parent (N));
+         Push_Scope (Id);
+         Process_Formals (Formals, Parent (N));
          End_Scope;
       end if;
-
    end Analyze_Entry_Body_Formal_Part;
 
    ------------------------------------
@@ -651,6 +906,8 @@ package body Sem_Ch9 is
    ------------------------------------
 
    procedure Analyze_Entry_Call_Alternative (N : Node_Id) is
+      Call : constant Node_Id := Entry_Call_Statement (N);
+
    begin
       Tasking_Used := True;
 
@@ -658,7 +915,17 @@ package body Sem_Ch9 is
          Analyze_List (Pragmas_Before (N));
       end if;
 
-      Analyze (Entry_Call_Statement (N));
+      if Nkind (Call) = N_Attribute_Reference then
+
+         --  Possibly a stream attribute, but definitely illegal. Other
+         --  illegalities, such as procedure calls, are diagnosed after
+         --  resolution.
+
+         Error_Msg_N ("entry call alternative requires an entry call", Call);
+         return;
+      end if;
+
+      Analyze (Call);
 
       if Is_Non_Empty_List (Statements (N)) then
          Analyze_Statements (Statements (N));
@@ -670,69 +937,79 @@ package body Sem_Ch9 is
    -------------------------------
 
    procedure Analyze_Entry_Declaration (N : Node_Id) is
-      Id      : Entity_Id := Defining_Identifier (N);
-      D_Sdef  : Node_Id   := Discrete_Subtype_Definition (N);
-      Formals : List_Id   := Parameter_Specifications (N);
+      D_Sdef  : constant Node_Id   := Discrete_Subtype_Definition (N);
+      Def_Id  : constant Entity_Id := Defining_Identifier (N);
+      Formals : constant List_Id   := Parameter_Specifications (N);
 
    begin
-      Generate_Definition (Id);
+      Generate_Definition (Def_Id);
       Tasking_Used := True;
 
       if No (D_Sdef) then
-         Set_Ekind (Id, E_Entry);
+         Set_Ekind (Def_Id, E_Entry);
       else
-         Enter_Name (Id);
-         Set_Ekind (Id, E_Entry_Family);
+         Enter_Name (Def_Id);
+         Set_Ekind (Def_Id, E_Entry_Family);
          Analyze (D_Sdef);
-         Make_Index (D_Sdef, N, Id);
+         Make_Index (D_Sdef, N, Def_Id);
       end if;
 
-      Set_Etype          (Id, Standard_Void_Type);
-      Set_Convention     (Id, Convention_Entry);
-      Set_Accept_Address (Id, New_Elmt_List);
+      Set_Etype          (Def_Id, Standard_Void_Type);
+      Set_Convention     (Def_Id, Convention_Entry);
+      Set_Accept_Address (Def_Id, New_Elmt_List);
 
       if Present (Formals) then
-         Set_Scope (Id, Current_Scope);
-         New_Scope (Id);
-         Process_Formals (Id, Formals, N);
-         Create_Extra_Formals (Id);
+         Set_Scope (Def_Id, Current_Scope);
+         Push_Scope (Def_Id);
+         Process_Formals (Formals, N);
+         Create_Extra_Formals (Def_Id);
          End_Scope;
       end if;
 
-      if Ekind (Id) = E_Entry then
-         New_Overloaded_Entity (Id);
+      if Ekind (Def_Id) = E_Entry then
+         New_Overloaded_Entity (Def_Id);
       end if;
 
+      Generate_Reference_To_Formals (Def_Id);
    end Analyze_Entry_Declaration;
 
    ---------------------------------------
    -- Analyze_Entry_Index_Specification --
    ---------------------------------------
 
-   --  The defining_Identifier of the entry index specification is local
-   --  to the entry body, but must be available in the entry barrier,
-   --  which is evaluated outside of the entry body. The index is eventually
-   --  renamed as a run-time object, so is visibility is strictly a front-end
-   --  concern. In order to make it available to the barrier, we create
-   --  an additional scope, as for a loop, whose only declaration is the
-   --  index name. This loop is not attached to the tree and does not appear
-   --  as an entity local to the protected type, so its existence need only
-   --  be knwown to routines that process entry families.
+   --  The Defining_Identifier of the entry index specification is local to the
+   --  entry body, but it must be available in the entry barrier which is
+   --  evaluated outside of the entry body. The index is eventually renamed as
+   --  a run-time object, so is visibility is strictly a front-end concern. In
+   --  order to make it available to the barrier, we create an additional
+   --  scope, as for a loop, whose only declaration is the index name. This
+   --  loop is not attached to the tree and does not appear as an entity local
+   --  to the protected type, so its existence need only be known to routines
+   --  that process entry families.
 
    procedure Analyze_Entry_Index_Specification (N : Node_Id) is
-      Iden    : constant Node_Id := Defining_Identifier (N);
-      Def     : constant Node_Id := Discrete_Subtype_Definition (N);
-      Loop_Id : Entity_Id :=
+      Iden    : constant Node_Id   := Defining_Identifier (N);
+      Def     : constant Node_Id   := Discrete_Subtype_Definition (N);
+      Loop_Id : constant Entity_Id :=
                   Make_Defining_Identifier (Sloc (N),
                     Chars => New_Internal_Name ('L'));
 
    begin
       Tasking_Used := True;
       Analyze (Def);
-      Make_Index (Def, N);
+
+      --  There is no elaboration of the entry index specification. Therefore,
+      --  if the index is a range, it is not resolved and expanded, but the
+      --  bounds are inherited from the entry declaration, and reanalyzed.
+      --  See Analyze_Entry_Body.
+
+      if Nkind (Def) /= N_Range then
+         Make_Index (Def, N);
+      end if;
+
       Set_Ekind (Loop_Id, E_Loop);
       Set_Scope (Loop_Id, Current_Scope);
-      New_Scope (Loop_Id);
+      Push_Scope (Loop_Id);
       Enter_Name (Iden);
       Set_Ekind (Iden, E_Entry_Index_Parameter);
       Set_Etype (Iden, Etype (Def));
@@ -743,9 +1020,20 @@ package body Sem_Ch9 is
    ----------------------------
 
    procedure Analyze_Protected_Body (N : Node_Id) is
-      Body_Id   : constant Entity_Id := Defining_Identifier (N);
-      Spec_Id   : Entity_Id;
-      Last_E    : Entity_Id;
+      Body_Id : constant Entity_Id := Defining_Identifier (N);
+      Last_E  : Entity_Id;
+
+      Spec_Id : Entity_Id;
+      --  This is initially the entity of the protected object or protected
+      --  type involved, but is replaced by the protected type always in the
+      --  case of a single protected declaration, since this is the proper
+      --  scope to be used.
+
+      Ref_Id : Entity_Id;
+      --  This is the entity of the protected object or protected type
+      --  involved, and is the entity used for cross-reference purposes (it
+      --  differs from Spec_Id in the case of a single protected object, since
+      --  Spec_Id is set to the protected type in this case).
 
    begin
       Tasking_Used := True;
@@ -768,7 +1056,8 @@ package body Sem_Ch9 is
          return;
       end if;
 
-      Generate_Reference (Spec_Id, Body_Id, 'b');
+      Ref_Id := Spec_Id;
+      Generate_Reference (Ref_Id, Body_Id, 'b', Set_Ref => False);
       Style.Check_Identifier (Body_Id, Spec_Id);
 
       --  The declarations are always attached to the type
@@ -777,21 +1066,21 @@ package body Sem_Ch9 is
          Spec_Id := Etype (Spec_Id);
       end if;
 
-      New_Scope (Spec_Id);
+      Push_Scope (Spec_Id);
       Set_Corresponding_Spec (N, Spec_Id);
       Set_Corresponding_Body (Parent (Spec_Id), Body_Id);
       Set_Has_Completion (Spec_Id);
       Install_Declarations (Spec_Id);
 
-      Exp_Ch9.Expand_Protected_Body_Declarations (N, Spec_Id);
+      Expand_Protected_Body_Declarations (N, Spec_Id);
 
       Last_E := Last_Entity (Spec_Id);
 
       Analyze_Declarations (Declarations (N));
 
-      --  For visibility purposes, all entities in the body are private.
-      --  Set First_Private_Entity accordingly, if there was no private
-      --  part in the protected declaration.
+      --  For visibility purposes, all entities in the body are private. Set
+      --  First_Private_Entity accordingly, if there was no private part in the
+      --  protected declaration.
 
       if No (First_Private_Entity (Spec_Id)) then
          if Present (Last_E) then
@@ -803,7 +1092,7 @@ package body Sem_Ch9 is
 
       Check_Completion (Body_Id);
       Check_References (Spec_Id);
-      Process_End_Label (N, 't');
+      Process_End_Label (N, 't', Ref_Id);
       End_Scope;
    end Analyze_Protected_Body;
 
@@ -815,6 +1104,55 @@ package body Sem_Ch9 is
       E : Entity_Id;
       L : Entity_Id;
 
+      procedure Undelay_Itypes (T : Entity_Id);
+      --  Itypes created for the private components of a protected type
+      --  do not receive freeze nodes, because there is no scope in which
+      --  they can be elaborated, and they can depend on discriminants of
+      --  the enclosed protected type. Given that the components can be
+      --  composite types with inner components, we traverse recursively
+      --  the private components of the protected type, and indicate that
+      --  all itypes within are frozen. This ensures that no freeze nodes
+      --  will be generated for them.
+      --
+      --  On the other hand, components of the corresponding record are
+      --  frozen (or receive itype references) as for other records.
+
+      --------------------
+      -- Undelay_Itypes --
+      --------------------
+
+      procedure Undelay_Itypes (T : Entity_Id) is
+         Comp : Entity_Id;
+
+      begin
+         if Is_Protected_Type (T) then
+            Comp := First_Private_Entity (T);
+         elsif Is_Record_Type (T) then
+            Comp := First_Entity (T);
+         else
+            return;
+         end if;
+
+         while Present (Comp) loop
+            if Is_Type (Comp)
+              and then Is_Itype (Comp)
+            then
+               Set_Has_Delayed_Freeze (Comp, False);
+               Set_Is_Frozen (Comp);
+
+               if Is_Record_Type (Comp)
+                 or else Is_Protected_Type (Comp)
+               then
+                  Undelay_Itypes (Comp);
+               end if;
+            end if;
+
+            Next_Entity (Comp);
+         end loop;
+      end Undelay_Itypes;
+
+   --  Start of processing for Analyze_Protected_Definition
+
    begin
       Tasking_Used := True;
       Analyze_Declarations (Visible_Declarations (N));
@@ -827,7 +1165,6 @@ package body Sem_Ch9 is
 
          if Present (L) then
             Set_First_Private_Entity (Current_Scope, Next_Entity (L));
-
          else
             Set_First_Private_Entity (Current_Scope,
               First_Entity (Current_Scope));
@@ -835,23 +1172,25 @@ package body Sem_Ch9 is
       end if;
 
       E := First_Entity (Current_Scope);
-
       while Present (E) loop
-
          if Ekind (E) = E_Function
            or else Ekind (E) = E_Procedure
          then
             Set_Convention (E, Convention_Protected);
 
-         elsif Is_Task_Type (Etype (E)) then
+         elsif Is_Task_Type (Etype (E))
+           or else Has_Task (Etype (E))
+         then
             Set_Has_Task (Current_Scope);
          end if;
 
          Next_Entity (E);
       end loop;
 
+      Undelay_Itypes (Current_Scope);
+
       Check_Max_Entries (N, Max_Protected_Entries);
-      Process_End_Label (N, 'e');
+      Process_End_Label (N, 'e', Current_Scope);
    end Analyze_Protected_Definition;
 
    ----------------------------
@@ -859,33 +1198,46 @@ package body Sem_Ch9 is
    ----------------------------
 
    procedure Analyze_Protected_Type (N : Node_Id) is
+      Def_Id : constant Entity_Id := Defining_Identifier (N);
       E      : Entity_Id;
       T      : Entity_Id;
-      Def_Id : constant Entity_Id := Defining_Identifier (N);
 
    begin
+      if No_Run_Time_Mode then
+         Error_Msg_CRT ("protected type", N);
+         return;
+      end if;
+
       Tasking_Used := True;
       Check_Restriction (No_Protected_Types, N);
 
       T := Find_Type_Name (N);
 
-      if Ekind (T) = E_Incomplete_Type then
+      --  In the case of an incomplete type, use the full view, unless it's not
+      --  present (as can occur for an incomplete view from a limited with).
+
+      if Ekind (T) = E_Incomplete_Type and then Present (Full_View (T)) then
          T := Full_View (T);
+         Set_Completion_Referenced (T);
       end if;
 
       Set_Ekind              (T, E_Protected_Type);
+      Set_Is_First_Subtype   (T, True);
       Init_Size_Align        (T);
       Set_Etype              (T, T);
-      Set_Is_First_Subtype   (T, True);
       Set_Has_Delayed_Freeze (T, True);
-      Set_Girder_Constraint  (T, No_Elist);
-      New_Scope (T);
+      Set_Stored_Constraint  (T, No_Elist);
+      Push_Scope (T);
+
+      if Ada_Version >= Ada_05 then
+         Check_Interfaces (N, T);
+      end if;
 
       if Present (Discriminant_Specifications (N)) then
          if Has_Discriminants (T) then
 
             --  Install discriminants. Also, verify conformance of
-            --  discriminants of previous and current view.  ???
+            --  discriminants of previous and current view. ???
 
             Install_Declarations (T);
          else
@@ -893,6 +1245,18 @@ package body Sem_Ch9 is
          end if;
       end if;
 
+      Set_Is_Constrained (T, not Has_Discriminants (T));
+
+      --  Perform minimal expansion of protected type while inside a generic.
+      --  The corresponding record is needed for various semantic checks.
+
+      if Ada_Version >= Ada_05
+        and then Inside_A_Generic
+      then
+         Insert_After_And_Analyze (N,
+           Build_Corresponding_Record (N, T, Sloc (T)));
+      end if;
+
       Analyze (Protected_Definition (N));
 
       --  Protected types with entries are controlled (because of the
@@ -900,7 +1264,7 @@ package body Sem_Ch9 is
       --  with interrupt handlers. Note that we need to analyze the protected
       --  definition to set Has_Entries and such.
 
-      if (Abort_Allowed or else Restrictions (No_Entry_Queue) = False
+      if (Abort_Allowed or else Restriction_Active (No_Entry_Queue) = False
            or else Number_Entries (T) > 1)
         and then
           (Has_Entries (T)
@@ -910,11 +1274,10 @@ package body Sem_Ch9 is
          Set_Has_Controlled_Component (T, True);
       end if;
 
-      --  The Ekind of components is E_Void during analysis to detect
-      --  illegal uses. Now it can be set correctly.
+      --  The Ekind of components is E_Void during analysis to detect illegal
+      --  uses. Now it can be set correctly.
 
       E := First_Entity (Current_Scope);
-
       while Present (E) loop
          if Ekind (E) = E_Void then
             Set_Ekind (E, E_Component);
@@ -926,15 +1289,31 @@ package body Sem_Ch9 is
 
       End_Scope;
 
+      --  Case of a completion of a private declaration
+
       if T /= Def_Id
         and then Is_Private_Type (Def_Id)
-        and then Has_Discriminants (Def_Id)
-        and then Expander_Active
       then
-         Exp_Ch9.Expand_N_Protected_Type_Declaration (N);
-         Process_Full_View (N, T, Def_Id);
-      end if;
+         --  Deal with preelaborable initialization. Note that this processing
+         --  is done by Process_Full_View, but as can be seen below, in this
+         --  case the call to Process_Full_View is skipped if any serious
+         --  errors have occurred, and we don't want to lose this check.
 
+         if Known_To_Have_Preelab_Init (Def_Id) then
+            Set_Must_Have_Preelab_Init (T);
+         end if;
+
+         --  Create corresponding record now, because some private dependents
+         --  may be subtypes of the partial view. Skip if errors are present,
+         --  to prevent cascaded messages.
+
+         if Serious_Errors_Detected = 0
+           and then Expander_Active
+         then
+            Expand_N_Protected_Type_Declaration (N);
+            Process_Full_View (N, T, Def_Id);
+         end if;
+      end if;
    end Analyze_Protected_Type;
 
    ---------------------
@@ -942,18 +1321,19 @@ package body Sem_Ch9 is
    ---------------------
 
    procedure Analyze_Requeue (N : Node_Id) is
-      Entry_Name : Node_Id := Name (N);
-      Entry_Id   : Entity_Id;
-      Found      : Boolean;
-      I          : Interp_Index;
-      It         : Interp;
-      Enclosing  : Entity_Id;
-      Target_Obj : Node_Id := Empty;
-      Req_Scope  : Entity_Id;
-      Outer_Ent  : Entity_Id;
+      Count       : Natural := 0;
+      Entry_Name  : Node_Id := Name (N);
+      Entry_Id    : Entity_Id;
+      I           : Interp_Index;
+      Is_Disp_Req : Boolean;
+      It          : Interp;
+      Enclosing   : Entity_Id;
+      Target_Obj  : Node_Id := Empty;
+      Req_Scope   : Entity_Id;
+      Outer_Ent   : Entity_Id;
 
    begin
-      Check_Restriction (No_Requeue, N);
+      Check_Restriction (No_Requeue_Statements, N);
       Check_Unreachable_Code (N);
       Tasking_Used := True;
 
@@ -981,13 +1361,13 @@ package body Sem_Ch9 is
          Entry_Name := Selector_Name (Entry_Name);
       end if;
 
-      --  If an explicit target object is given then we have to check
-      --  the restrictions of 9.5.4(6).
+      --  If an explicit target object is given then we have to check the
+      --  restrictions of 9.5.4(6).
 
       if Present (Target_Obj) then
-         --  Locate containing concurrent unit and determine
-         --  enclosing entry body or outermost enclosing accept
-         --  statement within the unit.
+
+         --  Locate containing concurrent unit and determine enclosing entry
+         --  body or outermost enclosing accept statement within the unit.
 
          Outer_Ent := Empty;
          for S in reverse 0 .. Scope_Stack.Last loop
@@ -1003,10 +1383,10 @@ package body Sem_Ch9 is
 
          pragma Assert (Present (Outer_Ent));
 
-         --  Check that the accessibility level of the target object
-         --  is not greater or equal to the outermost enclosing accept
-         --  statement (or entry body) unless it is a parameter of the
-         --  innermost enclosing accept statement (or entry body).
+         --  Check that the accessibility level of the target object is not
+         --  greater or equal to the outermost enclosing accept statement (or
+         --  entry body) unless it is a parameter of the innermost enclosing
+         --  accept statement (or entry body).
 
          if Object_Access_Level (Target_Obj) >= Scope_Depth (Outer_Ent)
            and then
@@ -1022,38 +1402,54 @@ package body Sem_Ch9 is
       --  Overloaded case, find right interpretation
 
       if Is_Overloaded (Entry_Name) then
-         Get_First_Interp (Entry_Name, I, It);
-         Found := False;
          Entry_Id := Empty;
 
+         --  Loop over candidate interpretations and filter out any that are
+         --  not parameterless, are not type conformant, are not entries, or
+         --  do not come from source.
+
+         Get_First_Interp (Entry_Name, I, It);
          while Present (It.Nam) loop
 
-            if No (First_Formal (It.Nam))
-              or else Subtype_Conformant (Enclosing, It.Nam)
+            --  Note: we test type conformance here, not subtype conformance.
+            --  Subtype conformance will be tested later on, but it is better
+            --  for error output in some cases not to do that here.
+
+            if (No (First_Formal (It.Nam))
+                 or else (Type_Conformant (Enclosing, It.Nam)))
+              and then Ekind (It.Nam) = E_Entry
             then
-               if not Found then
-                  Found := True;
+               --  Ada 2005 (AI-345): Since protected and task types have
+               --  primitive entry wrappers, we only consider source entries.
+
+               if Comes_From_Source (It.Nam) then
+                  Count := Count + 1;
                   Entry_Id := It.Nam;
                else
-                  Error_Msg_N ("ambiguous entry name in requeue", N);
-                  return;
+                  Remove_Interp (I);
                end if;
             end if;
 
             Get_Next_Interp (I, It);
          end loop;
 
-         if not Found then
-            Error_Msg_N ("no entry matches context",  N);
+         if Count = 0 then
+            Error_Msg_N ("no entry matches context", N);
             return;
+
+         elsif Count > 1 then
+            Error_Msg_N ("ambiguous entry name in requeue", N);
+            return;
+
          else
+            Set_Is_Overloaded (Entry_Name, False);
             Set_Entity (Entry_Name, Entry_Id);
          end if;
 
       --  Non-overloaded cases
 
-      --  For the case of a reference to an element of an entry family,
-      --  the Entry_Name is an indexed component.
+      --  For the case of a reference to an element of an entry family, the
+      --  Entry_Name is an indexed component.
 
       elsif Nkind (Entry_Name) = N_Indexed_Component then
 
@@ -1073,9 +1469,9 @@ package body Sem_Ch9 is
          end if;
 
       --  If we had a requeue of the form REQUEUE A (B), then the parser
-      --  accepted it (because it could have been a requeue on an entry
-      --  index. If A turns out not to be an entry family, then the analysis
-      --  of A (B) turned it into a function call.
+      --  accepted it (because it could have been a requeue on an entry index.
+      --  If A turns out not to be an entry family, then the analysis of A (B)
+      --  turned it into a function call.
 
       elsif Nkind (Entry_Name) = N_Function_Call then
          Error_Msg_N
@@ -1089,40 +1485,114 @@ package body Sem_Ch9 is
          Entry_Id := Entity (Entry_Name);
       end if;
 
+      --  Ada 2005 (AI05-0030): Potential dispatching requeue statement. The
+      --  target type must be a concurrent interface class-wide type and the
+      --  entry name must be a procedure, flagged by pragma Implemented_By_
+      --  Entry.
+
+      Is_Disp_Req :=
+        Ada_Version >= Ada_05
+          and then Present (Target_Obj)
+          and then Is_Class_Wide_Type (Etype (Target_Obj))
+          and then Is_Concurrent_Interface (Etype (Target_Obj))
+          and then Ekind (Entry_Id) = E_Procedure
+          and then Implemented_By_Entry (Entry_Id);
+
       --  Resolve entry, and check that it is subtype conformant with the
       --  enclosing construct if this construct has formals (RM 9.5.4(5)).
+      --  Ada 2005 (AI05-0030): Do not emit an error for this specific case.
 
-      if not Is_Entry (Entry_Id) then
+      if not Is_Entry (Entry_Id)
+        and then not Is_Disp_Req
+      then
          Error_Msg_N ("expect entry name in requeue statement", Name (N));
-      elsif Ekind (Entry_Id) = E_Entry_Family
 
+      elsif Ekind (Entry_Id) = E_Entry_Family
         and then Nkind (Entry_Name) /= N_Indexed_Component
       then
          Error_Msg_N ("missing index for entry family component", Name (N));
 
       else
          Resolve_Entry (Name (N));
+         Generate_Reference (Entry_Id, Entry_Name);
 
          if Present (First_Formal (Entry_Id)) then
-            Check_Subtype_Conformant (Enclosing, Entry_Id, Name (N));
+            if VM_Target = JVM_Target and then not Inspector_Mode then
+               Error_Msg_N
+                 ("arguments unsupported in requeue statement",
+                  First_Formal (Entry_Id));
+               return;
+            end if;
 
-            --  Mark any output parameters as assigned
+            --  Ada 2005 (AI05-0030): Perform type conformance after skipping
+            --  the first parameter of Entry_Id since it is the interface
+            --  controlling formal.
+
+            if Is_Disp_Req then
+               declare
+                  Enclosing_Formal : Entity_Id;
+                  Target_Formal    : Entity_Id;
+
+               begin
+                  Enclosing_Formal := First_Formal (Enclosing);
+                  Target_Formal := Next_Formal (First_Formal (Entry_Id));
+                  while Present (Enclosing_Formal)
+                    and then Present (Target_Formal)
+                  loop
+                     if not Conforming_Types
+                              (T1    => Etype (Enclosing_Formal),
+                               T2    => Etype (Target_Formal),
+                               Ctype => Subtype_Conformant)
+                     then
+                        Error_Msg_Node_2 := Target_Formal;
+                        Error_Msg_NE
+                          ("formal & is not subtype conformant with &" &
+                           "in dispatching requeue", N, Enclosing_Formal);
+                     end if;
+
+                     Next_Formal (Enclosing_Formal);
+                     Next_Formal (Target_Formal);
+                  end loop;
+               end;
+            else
+               Check_Subtype_Conformant (Enclosing, Entry_Id, Name (N));
+            end if;
+
+            --  Processing for parameters accessed by the requeue
 
             declare
-               Ent : Entity_Id := First_Formal (Enclosing);
+               Ent : Entity_Id;
 
             begin
+               Ent := First_Formal (Enclosing);
                while Present (Ent) loop
-                  if Ekind (Ent) = E_Out_Parameter then
-                     Set_Not_Source_Assigned (Ent, False);
+
+                  --  For OUT or IN OUT parameter, the effect of the requeue is
+                  --  to assign the parameter a value on exit from the requeued
+                  --  body, so we can set it as source assigned. We also clear
+                  --  the Is_True_Constant indication. We do not need to clear
+                  --  Current_Value, since the effect of the requeue is to
+                  --  perform an unconditional goto so that any further
+                  --  references will not occur anyway.
+
+                  if Ekind (Ent) = E_Out_Parameter
+                       or else
+                     Ekind (Ent) = E_In_Out_Parameter
+                  then
+                     Set_Never_Set_In_Source (Ent, False);
+                     Set_Is_True_Constant    (Ent, False);
                   end if;
 
+                  --  For all parameters, the requeue acts as a reference,
+                  --  since the value of the parameter is passed to the new
+                  --  entry, so we want to suppress unreferenced warnings.
+
+                  Set_Referenced (Ent);
                   Next_Formal (Ent);
                end loop;
             end;
          end if;
       end if;
-
    end Analyze_Requeue;
 
    ------------------------------
@@ -1143,6 +1613,8 @@ package body Sem_Ch9 is
       Check_Restriction (No_Select_Statements, N);
       Tasking_Used := True;
 
+      --  Loop to analyze alternatives
+
       Alt := First (Alts);
       while Present (Alt) loop
          Alt_Count := Alt_Count + 1;
@@ -1151,8 +1623,8 @@ package body Sem_Ch9 is
          if Nkind (Alt) = N_Delay_Alternative then
             if Delay_Present then
 
-               if (Relative_Present /=
-                 (Nkind (Delay_Statement (Alt)) = N_Delay_Relative_Statement))
+               if Relative_Present /=
+                   (Nkind (Delay_Statement (Alt)) = N_Delay_Relative_Statement)
                then
                   Error_Msg_N
                     ("delay_until and delay_relative alternatives ", Alt);
@@ -1168,7 +1640,7 @@ package body Sem_Ch9 is
 
          elsif Nkind (Alt) = N_Terminate_Alternative then
             if Terminate_Present then
-               Error_Msg_N ("Only one terminate alternative allowed", N);
+               Error_Msg_N ("only one terminate alternative allowed", N);
             else
                Terminate_Present := True;
                Check_Restriction (No_Terminate_Alternatives, N);
@@ -1223,7 +1695,7 @@ package body Sem_Ch9 is
          Next (Alt);
       end loop;
 
-      Check_Restriction (Max_Select_Alternatives, Alt_Count, N);
+      Check_Restriction (Max_Select_Alternatives, N, Alt_Count);
       Check_Potentially_Blocking_Operation (N);
 
       if Terminate_Present and Delay_Present then
@@ -1253,14 +1725,14 @@ package body Sem_Ch9 is
       T      : Entity_Id;
       T_Decl : Node_Id;
       O_Decl : Node_Id;
-      O_Name : constant Entity_Id := New_Copy (Id);
+      O_Name : constant Entity_Id := Id;
 
    begin
       Generate_Definition (Id);
       Tasking_Used := True;
 
-      --  The node is rewritten as a protected type declaration,
-      --  in exact analogy with what is done with single tasks.
+      --  The node is rewritten as a protected type declaration, in exact
+      --  analogy with what is done with single tasks.
 
       T :=
         Make_Defining_Identifier (Sloc (Id),
@@ -1269,7 +1741,8 @@ package body Sem_Ch9 is
       T_Decl :=
         Make_Protected_Type_Declaration (Loc,
          Defining_Identifier => T,
-         Protected_Definition => Relocate_Node (Protected_Definition (N)));
+         Protected_Definition => Relocate_Node (Protected_Definition (N)),
+         Interface_List       => Interface_List (N));
 
       O_Decl :=
         Make_Object_Declaration (Loc,
@@ -1280,8 +1753,8 @@ package body Sem_Ch9 is
       Insert_After (N, O_Decl);
       Mark_Rewrite_Insertion (O_Decl);
 
-      --  Enter names of type and object before analysis, because the name
-      --  of the object may be used in its own body.
+      --  Enter names of type and object before analysis, because the name of
+      --  the object may be used in its own body.
 
       Enter_Name (T);
       Set_Ekind (T, E_Protected_Type);
@@ -1291,12 +1764,11 @@ package body Sem_Ch9 is
       Set_Ekind (O_Name, E_Variable);
       Set_Etype (O_Name, T);
 
-      --  Instead of calling Analyze on the new node,  call directly
-      --  the proper analysis procedure. Otherwise the node would be
-      --  expanded twice, with disastrous result.
+      --  Instead of calling Analyze on the new node, call the proper analysis
+      --  procedure directly. Otherwise the node would be expanded twice, with
+      --  disastrous result.
 
       Analyze_Protected_Type (N);
-
    end Analyze_Single_Protected;
 
    -------------------------
@@ -1309,14 +1781,14 @@ package body Sem_Ch9 is
       T      : Entity_Id;
       T_Decl : Node_Id;
       O_Decl : Node_Id;
-      O_Name : constant Entity_Id := New_Copy (Id);
+      O_Name : constant Entity_Id := Id;
 
    begin
       Generate_Definition (Id);
       Tasking_Used := True;
 
-      --  The node is rewritten as a task type declaration,  followed
-      --  by an object declaration of that anonymous task type.
+      --  The node is rewritten as a task type declaration, followed by an
+      --  object declaration of that anonymous task type.
 
       T :=
         Make_Defining_Identifier (Sloc (Id),
@@ -1325,7 +1797,16 @@ package body Sem_Ch9 is
       T_Decl :=
         Make_Task_Type_Declaration (Loc,
           Defining_Identifier => T,
-          Task_Definition     => Relocate_Node (Task_Definition (N)));
+          Task_Definition     => Relocate_Node (Task_Definition (N)),
+          Interface_List      => Interface_List (N));
+
+      --  We use the original defining identifier of the single task in the
+      --  generated object declaration, so that debugging information can
+      --  be attached to it when compiling with -gnatD. The parent of the
+      --  entity is the new object declaration. The single_task_declaration
+      --  is not used further in semantics or code generation, but is scanned
+      --  when generating debug information, and therefore needs the updated
+      --  Sloc information for the entity (see Sprint).
 
       O_Decl :=
         Make_Object_Declaration (Loc,
@@ -1336,8 +1817,8 @@ package body Sem_Ch9 is
       Insert_After (N, O_Decl);
       Mark_Rewrite_Insertion (O_Decl);
 
-      --  Enter names of type and object before analysis, because the name
-      --  of the object may be used in its own body.
+      --  Enter names of type and object before analysis, because the name of
+      --  the object may be used in its own body.
 
       Enter_Name (T);
       Set_Ekind (T, E_Task_Type);
@@ -1347,12 +1828,11 @@ package body Sem_Ch9 is
       Set_Ekind (O_Name, E_Variable);
       Set_Etype (O_Name, T);
 
-      --  Instead of calling Analyze on the new node,  call directly
-      --  the proper analysis procedure. Otherwise the node would be
-      --  expanded twice, with disastrous result.
+      --  Instead of calling Analyze on the new node, call the proper analysis
+      --  procedure directly. Otherwise the node would be expanded twice, with
+      --  disastrous result.
 
       Analyze_Task_Type (N);
-
    end Analyze_Single_Task;
 
    -----------------------
@@ -1361,9 +1841,20 @@ package body Sem_Ch9 is
 
    procedure Analyze_Task_Body (N : Node_Id) is
       Body_Id : constant Entity_Id := Defining_Identifier (N);
-      Spec_Id : Entity_Id;
+      Decls   : constant List_Id   := Declarations (N);
+      HSS     : constant Node_Id   := Handled_Statement_Sequence (N);
       Last_E  : Entity_Id;
 
+      Spec_Id : Entity_Id;
+      --  This is initially the entity of the task or task type involved, but
+      --  is replaced by the task type always in the case of a single task
+      --  declaration, since this is the proper scope to be used.
+
+      Ref_Id : Entity_Id;
+      --  This is the entity of the task or task type, and is the entity used
+      --  for cross-reference purposes (it differs from Spec_Id in the case of
+      --  a single task, since Spec_Id is set to the task type)
+
    begin
       Tasking_Used := True;
       Set_Ekind (Body_Id, E_Task_Body);
@@ -1389,7 +1880,19 @@ package body Sem_Ch9 is
          return;
       end if;
 
-      Generate_Reference (Spec_Id, Body_Id, 'b');
+      if Has_Completion (Spec_Id)
+        and then Present (Corresponding_Body (Parent (Spec_Id)))
+      then
+         if Nkind (Parent (Spec_Id)) = N_Task_Type_Declaration then
+            Error_Msg_NE ("duplicate body for task type&", N, Spec_Id);
+
+         else
+            Error_Msg_NE ("duplicate body for task&", N, Spec_Id);
+         end if;
+      end if;
+
+      Ref_Id := Spec_Id;
+      Generate_Reference (Ref_Id, Body_Id, 'b', Set_Ref => False);
       Style.Check_Identifier (Body_Id, Spec_Id);
 
       --  Deal with case of body of single task (anonymous type was created)
@@ -1398,18 +1901,19 @@ package body Sem_Ch9 is
          Spec_Id := Etype (Spec_Id);
       end if;
 
-      New_Scope (Spec_Id);
+      Push_Scope (Spec_Id);
       Set_Corresponding_Spec (N, Spec_Id);
       Set_Corresponding_Body (Parent (Spec_Id), Body_Id);
       Set_Has_Completion (Spec_Id);
       Install_Declarations (Spec_Id);
       Last_E := Last_Entity (Spec_Id);
 
-      Analyze_Declarations (Declarations (N));
+      Analyze_Declarations (Decls);
+      Inspect_Deferred_Constant_Completion (Decls);
 
-      --  For visibility purposes, all entities in the body are private.
-      --  Set First_Private_Entity accordingly, if there was no private
-      --  part in the protected declaration.
+      --  For visibility purposes, all entities in the body are private. Set
+      --  First_Private_Entity accordingly, if there was no private part in the
+      --  protected declaration.
 
       if No (First_Private_Entity (Spec_Id)) then
          if Present (Last_E) then
@@ -1419,9 +1923,27 @@ package body Sem_Ch9 is
          end if;
       end if;
 
-      Analyze (Handled_Statement_Sequence (N));
+      --  Mark all handlers as not suitable for local raise optimization,
+      --  since this optimization causes difficulties in a task context.
+
+      if Present (Exception_Handlers (HSS)) then
+         declare
+            Handlr : Node_Id;
+         begin
+            Handlr := First (Exception_Handlers (HSS));
+            while Present (Handlr) loop
+               Set_Local_Raise_Not_OK (Handlr);
+               Next (Handlr);
+            end loop;
+         end;
+      end if;
+
+      --  Now go ahead and complete analysis of the task body
+
+      Analyze (HSS);
       Check_Completion (Body_Id);
       Check_References (Body_Id);
+      Check_References (Spec_Id);
 
       --  Check for entries with no corresponding accept
 
@@ -1430,7 +1952,6 @@ package body Sem_Ch9 is
 
       begin
          Ent := First_Entity (Spec_Id);
-
          while Present (Ent) loop
             if Is_Entry (Ent)
               and then not Entry_Accepted (Ent)
@@ -1443,7 +1964,7 @@ package body Sem_Ch9 is
          end loop;
       end;
 
-      Process_End_Label (Handled_Statement_Sequence (N), 't');
+      Process_End_Label (HSS, 't', Ref_Id);
       End_Scope;
    end Analyze_Task_Body;
 
@@ -1475,7 +1996,7 @@ package body Sem_Ch9 is
       end if;
 
       Check_Max_Entries (N, Max_Task_Entries);
-      Process_End_Label (N, 'e');
+      Process_End_Label (N, 'e', Current_Scope);
    end Analyze_Task_Definition;
 
    -----------------------
@@ -1483,17 +2004,21 @@ package body Sem_Ch9 is
    -----------------------
 
    procedure Analyze_Task_Type (N : Node_Id) is
-      T      : Entity_Id;
       Def_Id : constant Entity_Id := Defining_Identifier (N);
+      T      : Entity_Id;
 
    begin
+      Check_Restriction (No_Tasking, N);
       Tasking_Used := True;
-      Check_Restriction (Max_Tasks, N);
       T := Find_Type_Name (N);
       Generate_Definition (T);
 
-      if Ekind (T) = E_Incomplete_Type then
+      --  In the case of an incomplete type, use the full view, unless it's not
+      --  present (as can occur for an incomplete view from a limited with).
+
+      if Ekind (T) = E_Incomplete_Type and then Present (Full_View (T)) then
          T := Full_View (T);
+         Set_Completion_Referenced (T);
       end if;
 
       Set_Ekind              (T, E_Task_Type);
@@ -1502,18 +2027,22 @@ package body Sem_Ch9 is
       Init_Size_Align        (T);
       Set_Etype              (T, T);
       Set_Has_Delayed_Freeze (T, True);
-      Set_Girder_Constraint (T, No_Elist);
-      New_Scope (T);
+      Set_Stored_Constraint  (T, No_Elist);
+      Push_Scope (T);
+
+      if Ada_Version >= Ada_05 then
+         Check_Interfaces (N, T);
+      end if;
 
       if Present (Discriminant_Specifications (N)) then
-         if Ada_83 and then Comes_From_Source (N) then
+         if Ada_Version = Ada_83 and then Comes_From_Source (N) then
             Error_Msg_N ("(Ada 83) task discriminant not allowed!", N);
          end if;
 
          if Has_Discriminants (T) then
 
             --  Install discriminants. Also, verify conformance of
-            --  discriminants of previous and current view.  ???
+            --  discriminants of previous and current view. ???
 
             Install_Declarations (T);
          else
@@ -1521,6 +2050,17 @@ package body Sem_Ch9 is
          end if;
       end if;
 
+      Set_Is_Constrained (T, not Has_Discriminants (T));
+
+      --  Perform minimal expansion of the task type while inside a generic
+      --  context. The corresponding record is needed for various semantic
+      --  checks.
+
+      if Inside_A_Generic then
+         Insert_After_And_Analyze (N,
+           Build_Corresponding_Record (N, T, Sloc (T)));
+      end if;
+
       if Present (Task_Definition (N)) then
          Analyze_Task_Definition (Task_Definition (N));
       end if;
@@ -1531,13 +2071,30 @@ package body Sem_Ch9 is
 
       End_Scope;
 
+      --  Case of a completion of a private declaration
+
       if T /= Def_Id
         and then Is_Private_Type (Def_Id)
-        and then Has_Discriminants (Def_Id)
-        and then Expander_Active
       then
-         Exp_Ch9.Expand_N_Task_Type_Declaration (N);
-         Process_Full_View (N, T, Def_Id);
+         --  Deal with preelaborable initialization. Note that this processing
+         --  is done by Process_Full_View, but as can be seen below, in this
+         --  case the call to Process_Full_View is skipped if any serious
+         --  errors have occurred, and we don't want to lose this check.
+
+         if Known_To_Have_Preelab_Init (Def_Id) then
+            Set_Must_Have_Preelab_Init (T);
+         end if;
+
+         --  Create corresponding record now, because some private dependents
+         --  may be subtypes of the partial view. Skip if errors are present,
+         --  to prevent cascaded messages.
+
+         if Serious_Errors_Detected = 0
+           and then Expander_Active
+         then
+            Expand_N_Task_Type_Declaration (N);
+            Process_Full_View (N, T, Def_Id);
+         end if;
       end if;
    end Analyze_Task_Type;
 
@@ -1563,11 +2120,36 @@ package body Sem_Ch9 is
    ------------------------------
 
    procedure Analyze_Timed_Entry_Call (N : Node_Id) is
+      Trigger        : constant Node_Id :=
+                         Entry_Call_Statement (Entry_Call_Alternative (N));
+      Is_Disp_Select : Boolean := False;
+
    begin
       Check_Restriction (No_Select_Statements, N);
       Tasking_Used := True;
-      Analyze (Entry_Call_Alternative (N));
-      Analyze (Delay_Alternative (N));
+
+      --  Ada 2005 (AI-345): The trigger may be a dispatching call
+
+      if Ada_Version >= Ada_05 then
+         Analyze (Trigger);
+         Check_Triggering_Statement (Trigger, N, Is_Disp_Select);
+      end if;
+
+      --  Postpone the analysis of the statements till expansion. Analyze only
+      --  if the expander is disabled in order to catch any semantic errors.
+
+      if Is_Disp_Select then
+         if not Expander_Active then
+            Analyze (Entry_Call_Alternative (N));
+            Analyze (Delay_Alternative (N));
+         end if;
+
+      --  Regular select analysis
+
+      else
+         Analyze (Entry_Call_Alternative (N));
+         Analyze (Delay_Alternative (N));
+      end if;
    end Analyze_Timed_Entry_Call;
 
    ------------------------------------
@@ -1575,7 +2157,8 @@ package body Sem_Ch9 is
    ------------------------------------
 
    procedure Analyze_Triggering_Alternative (N : Node_Id) is
-      Trigger : Node_Id := Triggering_Statement (N);
+      Trigger : constant Node_Id := Triggering_Statement (N);
+
    begin
       Tasking_Used := True;
 
@@ -1584,13 +2167,29 @@ package body Sem_Ch9 is
       end if;
 
       Analyze (Trigger);
+
       if Comes_From_Source (Trigger)
-        and then Nkind (Trigger) /= N_Delay_Until_Statement
-        and then Nkind (Trigger) /= N_Delay_Relative_Statement
+        and then Nkind (Trigger) not in N_Delay_Statement
         and then Nkind (Trigger) /= N_Entry_Call_Statement
       then
-         Error_Msg_N
-          ("triggering statement must be delay or entry call", Trigger);
+         if Ada_Version < Ada_05 then
+            Error_Msg_N
+             ("triggering statement must be delay or entry call", Trigger);
+
+         --  Ada 2005 (AI-345): If a procedure_call_statement is used for a
+         --  procedure_or_entry_call, the procedure_name or procedure_prefix
+         --  of the procedure_call_statement shall denote an entry renamed by a
+         --  procedure, or (a view of) a primitive subprogram of a limited
+         --  interface whose first parameter is a controlling parameter.
+
+         elsif Nkind (Trigger) = N_Procedure_Call_Statement
+           and then not Is_Renamed_Entry (Entity (Name (Trigger)))
+           and then not Is_Controlling_Limited_Procedure
+                          (Entity (Name (Trigger)))
+         then
+            Error_Msg_N ("triggering statement must be delay, procedure " &
+                         "or entry call", Trigger);
+         end if;
       end if;
 
       if Is_Non_Empty_List (Statements (N)) then
@@ -1602,12 +2201,16 @@ package body Sem_Ch9 is
    -- Check_Max_Entries --
    -----------------------
 
-   procedure Check_Max_Entries (Def : Node_Id; R : Restriction_Parameter_Id) is
+   procedure Check_Max_Entries (D : Node_Id; R : All_Parameter_Restrictions) is
       Ecount : Uint;
 
       procedure Count (L : List_Id);
       --  Count entries in given declaration list
 
+      -----------
+      -- Count --
+      -----------
+
       procedure Count (L : List_Id) is
          D : Node_Id;
 
@@ -1624,9 +2227,13 @@ package body Sem_Ch9 is
                           Discrete_Subtype_Definition (D);
 
                begin
+                  --  If not an entry family, then just one entry
+
                   if No (DSD) then
                      Ecount := Ecount + 1;
 
+                  --  If entry family with static bounds, count entries
+
                   elsif Is_OK_Static_Subtype (Etype (DSD)) then
                      declare
                         Lo : constant Uint :=
@@ -1642,9 +2249,21 @@ package body Sem_Ch9 is
                         end if;
                      end;
 
+                  --  Entry family with non-static bounds
+
                   else
-                     Error_Msg_N
-                       ("static subtype required by Restriction pragma", DSD);
+                     --  If restriction is set, then this is an error
+
+                     if Restrictions.Set (R) then
+                        Error_Msg_N
+                          ("static subtype required by Restriction pragma",
+                           DSD);
+
+                     --  Otherwise we record an unknown count restriction
+
+                     else
+                        Check_Restriction (R, D);
+                     end if;
                   end if;
                end;
             end if;
@@ -1656,14 +2275,215 @@ package body Sem_Ch9 is
    --  Start of processing for Check_Max_Entries
 
    begin
-      if Restriction_Parameters (R) >= 0 then
-         Ecount := Uint_0;
-         Count (Visible_Declarations (Def));
-         Count (Private_Declarations (Def));
-         Check_Restriction (R, Ecount, Def);
+      Ecount := Uint_0;
+      Count (Visible_Declarations (D));
+      Count (Private_Declarations (D));
+
+      if Ecount > 0 then
+         Check_Restriction (R, D, Ecount);
       end if;
    end Check_Max_Entries;
 
+   ----------------------
+   -- Check_Interfaces --
+   ----------------------
+
+   procedure Check_Interfaces (N : Node_Id; T : Entity_Id) is
+      Iface     : Node_Id;
+      Iface_Typ : Entity_Id;
+
+   begin
+      pragma Assert
+        (Nkind_In (N, N_Protected_Type_Declaration, N_Task_Type_Declaration));
+
+      if Present (Interface_List (N)) then
+         Set_Is_Tagged_Type (T);
+
+         Iface := First (Interface_List (N));
+         while Present (Iface) loop
+            Iface_Typ := Find_Type_Of_Subtype_Indic (Iface);
+
+            if not Is_Interface (Iface_Typ) then
+               Error_Msg_NE
+                 ("(Ada 2005) & must be an interface", Iface, Iface_Typ);
+
+            else
+               --  Ada 2005 (AI-251): "The declaration of a specific descendant
+               --  of an interface type freezes the interface type" RM 13.14.
+
+               Freeze_Before (N, Etype (Iface));
+
+               if Nkind (N) = N_Protected_Type_Declaration then
+
+                  --  Ada 2005 (AI-345): Protected types can only implement
+                  --  limited, synchronized, or protected interfaces (note that
+                  --  the predicate Is_Limited_Interface includes synchronized
+                  --  and protected interfaces).
+
+                  if Is_Task_Interface (Iface_Typ) then
+                     Error_Msg_N ("(Ada 2005) protected type cannot implement "
+                       & "a task interface", Iface);
+
+                  elsif not Is_Limited_Interface (Iface_Typ) then
+                     Error_Msg_N ("(Ada 2005) protected type cannot implement "
+                       & "a non-limited interface", Iface);
+                  end if;
+
+               else pragma Assert (Nkind (N) = N_Task_Type_Declaration);
+
+                  --  Ada 2005 (AI-345): Task types can only implement limited,
+                  --  synchronized, or task interfaces (note that the predicate
+                  --  Is_Limited_Interface includes synchronized and task
+                  --  interfaces).
+
+                  if Is_Protected_Interface (Iface_Typ) then
+                     Error_Msg_N ("(Ada 2005) task type cannot implement a " &
+                       "protected interface", Iface);
+
+                  elsif not Is_Limited_Interface (Iface_Typ) then
+                     Error_Msg_N ("(Ada 2005) task type cannot implement a " &
+                       "non-limited interface", Iface);
+                  end if;
+               end if;
+            end if;
+
+            Next (Iface);
+         end loop;
+      end if;
+
+      if not Has_Private_Declaration (T) then
+         return;
+      end if;
+
+      --  Additional checks on full-types associated with private type
+      --  declarations. Search for the private type declaration.
+
+      declare
+         Full_T_Ifaces : Elist_Id;
+         Iface         : Node_Id;
+         Priv_T        : Entity_Id;
+         Priv_T_Ifaces : Elist_Id;
+
+      begin
+         Priv_T := First_Entity (Scope (T));
+         loop
+            pragma Assert (Present (Priv_T));
+
+            if Is_Type (Priv_T) and then Present (Full_View (Priv_T)) then
+               exit when Full_View (Priv_T) = T;
+            end if;
+
+            Next_Entity (Priv_T);
+         end loop;
+
+         --  In case of synchronized types covering interfaces the private type
+         --  declaration must be limited.
+
+         if Present (Interface_List (N))
+           and then not Is_Limited_Record (Priv_T)
+         then
+            Error_Msg_Sloc := Sloc (Priv_T);
+            Error_Msg_N ("(Ada 2005) limited type declaration expected for " &
+                         "private type#", T);
+         end if;
+
+         --  RM 7.3 (7.1/2): If the full view has a partial view that is
+         --  tagged then check RM 7.3 subsidiary rules.
+
+         if Is_Tagged_Type (Priv_T)
+           and then not Error_Posted (N)
+         then
+            --  RM 7.3 (7.2/2): The partial view shall be a synchronized tagged
+            --  type if and only if the full type is a synchronized tagged type
+
+            if Is_Synchronized_Tagged_Type (Priv_T)
+              and then not Is_Synchronized_Tagged_Type (T)
+            then
+               Error_Msg_N
+                 ("(Ada 2005) full view must be a synchronized tagged " &
+                  "type (RM 7.3 (7.2/2))", Priv_T);
+
+            elsif Is_Synchronized_Tagged_Type (T)
+              and then not Is_Synchronized_Tagged_Type (Priv_T)
+            then
+               Error_Msg_N
+                 ("(Ada 2005) partial view must be a synchronized tagged " &
+                  "type (RM 7.3 (7.2/2))", T);
+            end if;
+
+            --  RM 7.3 (7.3/2): The partial view shall be a descendant of an
+            --  interface type if and only if the full type is descendant of
+            --  the interface type.
+
+            if Present (Interface_List (N))
+              or else (Is_Tagged_Type (Priv_T)
+                         and then Has_Interfaces
+                                   (Priv_T, Use_Full_View => False))
+            then
+               if Is_Tagged_Type (Priv_T) then
+                  Collect_Interfaces
+                    (Priv_T, Priv_T_Ifaces, Use_Full_View => False);
+               end if;
+
+               if Is_Tagged_Type (T) then
+                  Collect_Interfaces (T, Full_T_Ifaces);
+               end if;
+
+               Iface := Find_Hidden_Interface (Priv_T_Ifaces, Full_T_Ifaces);
+
+               if Present (Iface) then
+                  Error_Msg_NE ("interface & not implemented by full type " &
+                                "(RM-2005 7.3 (7.3/2))", Priv_T, Iface);
+               end if;
+
+               Iface := Find_Hidden_Interface (Full_T_Ifaces, Priv_T_Ifaces);
+
+               if Present (Iface) then
+                  Error_Msg_NE ("interface & not implemented by partial " &
+                                "view (RM-2005 7.3 (7.3/2))", T, Iface);
+               end if;
+            end if;
+         end if;
+      end;
+   end Check_Interfaces;
+
+   --------------------------------
+   -- Check_Triggering_Statement --
+   --------------------------------
+
+   procedure Check_Triggering_Statement
+     (Trigger        : Node_Id;
+      Error_Node     : Node_Id;
+      Is_Dispatching : out Boolean)
+   is
+      Param : Node_Id;
+
+   begin
+      Is_Dispatching := False;
+
+      --  It is not possible to have a dispatching trigger if we are not in
+      --  Ada 2005 mode.
+
+      if Ada_Version >= Ada_05
+        and then Nkind (Trigger) = N_Procedure_Call_Statement
+        and then Present (Parameter_Associations (Trigger))
+      then
+         Param := First (Parameter_Associations (Trigger));
+
+         if Is_Controlling_Actual (Param)
+           and then Is_Interface (Etype (Param))
+         then
+            if Is_Limited_Record (Etype (Param)) then
+               Is_Dispatching := True;
+            else
+               Error_Msg_N
+                 ("dispatching operation of limited or synchronized " &
+                  "interface required (RM 9.7.2(3))!", Error_Node);
+            end if;
+         end if;
+      end if;
+   end Check_Triggering_Statement;
+
    --------------------------
    -- Find_Concurrent_Spec --
    --------------------------
@@ -1689,10 +2509,8 @@ package body Sem_Ch9 is
    procedure Install_Declarations (Spec : Entity_Id) is
       E    : Entity_Id;
       Prev : Entity_Id;
-
    begin
       E := First_Entity (Spec);
-
       while Present (E) loop
          Prev := Current_Entity (E);
          Set_Current_Entity (E);