From 53b10ce9218f53b3a0b139133cf95ab31c7cc344 Mon Sep 17 00:00:00 2001
From: Arnaud Charlet <charlet@gcc.gnu.org>
Date: Wed, 29 Jul 2009 10:44:57 +0200
Subject: [PATCH] [multiple changes]

2009-07-29  Ed Schonberg  <schonberg@adacore.com>

	* sem_ch6.adb (Check_Overriding_Indicator): Handle properly overriding
	indicators on user-defined operators.

2009-07-29  Vadim Godunko  <godunko@adacore.com>

	* g-socket.adb (Receive_Vector): Add comment.

From-SVN: r150200
---
 gcc/ada/ChangeLog    |  9 +++++
 gcc/ada/g-socket.adb |  3 ++
 gcc/ada/sem_ch6.adb  | 96 ++++++++++++++++++++++++++------------------
 3 files changed, 69 insertions(+), 39 deletions(-)

diff --git a/gcc/ada/ChangeLog b/gcc/ada/ChangeLog
index 6c2f298edb7b..d2f86f65a96a 100644
--- a/gcc/ada/ChangeLog
+++ b/gcc/ada/ChangeLog
@@ -1,3 +1,12 @@
+2009-07-29  Ed Schonberg  <schonberg@adacore.com>
+
+	* sem_ch6.adb (Check_Overriding_Indicator): Handle properly overriding
+	indicators on user-defined operators.
+
+2009-07-29  Vadim Godunko  <godunko@adacore.com>
+
+	* g-socket.adb (Receive_Vector): Add comment.
+
 2009-07-29  Javier Miranda  <miranda@adacore.com>
 
 	* frontend.adb (Frontend): Code cleanup.
diff --git a/gcc/ada/g-socket.adb b/gcc/ada/g-socket.adb
index c816312ac3f0..90d36f6dc59c 100644
--- a/gcc/ada/g-socket.adb
+++ b/gcc/ada/g-socket.adb
@@ -1666,6 +1666,9 @@ package body GNAT.Sockets is
                Msg_Iov        => Vector'Address,
                Msg_Iovlen     =>
                  SOSC.Msg_Iovlen_T'Min (Vector'Length, SOSC.IOV_MAX),
+               --  recvmsg(2) returns EMSGSIZE on Linux (and probably on other
+               --  platforms) when the supplied vector is longer than IOV_MAX,
+               --  so use minimum of the two lengths.
                Msg_Control    => System.Null_Address,
                Msg_Controllen => 0,
                Msg_Flags      => 0);
diff --git a/gcc/ada/sem_ch6.adb b/gcc/ada/sem_ch6.adb
index 33ac2e66063d..c72b3137ef84 100644
--- a/gcc/ada/sem_ch6.adb
+++ b/gcc/ada/sem_ch6.adb
@@ -4375,6 +4375,13 @@ package body Sem_Ch6 is
       elsif Ekind (Subp) = E_Entry then
          Decl := Parent (Subp);
 
+         --  No point in analyzing a malformed operator
+
+      elsif Nkind (Subp) = N_Defining_Operator_Symbol
+        and then Error_Posted (Subp)
+      then
+         return;
+
       else
          Decl := Unit_Declaration_Node (Subp);
       end if;
@@ -4476,7 +4483,8 @@ package body Sem_Ch6 is
             Style.Missing_Overriding (Decl, Subp);
          end if;
 
-      --  If Subp is an operator, it may override a predefined operation.
+      --  If Subp is an operator, it may override a predefined operation, if
+      --  it is defined in the same scope as the type to which it applies.
       --  In that case overridden_subp is empty because of our implicit
       --  representation for predefined operators. We have to check whether the
       --  signature of Subp matches that of a predefined operator. Note that
@@ -4487,54 +4495,64 @@ package body Sem_Ch6 is
       --  explicit overridden operation.
 
       elsif Nkind (Subp) = N_Defining_Operator_Symbol then
+         declare
+            Typ          : constant Entity_Id :=
+                             Base_Type (Etype (First_Formal (Subp)));
+            Can_Override : constant Boolean :=
+              Operator_Matches_Spec (Subp, Subp)
+                and then Scope (Subp) = Scope (Typ)
+                and then not Is_Class_Wide_Type (Typ);
 
-         if Must_Not_Override (Spec) then
+         begin
+            if Must_Not_Override (Spec) then
 
-            --  If this is not a primitive operation or protected subprogram,
-            --  then "not overriding" is illegal.
+               --  If this is not a primitive or a protected subprogram,
+               --  then "not overriding" is illegal.
 
-            if not Is_Primitive
-              and then Ekind (Scope (Subp)) /= E_Protected_Type
-            then
-               Error_Msg_N
-                 ("overriding indicator only allowed "
-                    & "if subprogram is primitive", Subp);
+               if not Is_Primitive
+                 and then Ekind (Scope (Subp)) /= E_Protected_Type
+               then
+                  Error_Msg_N
+                    ("overriding indicator only allowed "
+                       & "if subprogram is primitive", Subp);
 
-            elsif Operator_Matches_Spec (Subp, Subp) then
-               Error_Msg_NE
-                 ("subprogram & overrides predefined operator ", Spec, Subp);
-            end if;
+               elsif Can_Override then
+                  Error_Msg_NE
+                    ("subprogram & overrides predefined operator ",
+                       Spec, Subp);
+               end if;
 
-         elsif Must_Override (Spec) then
-            if Is_Overriding_Operation (Subp) then
-               Set_Is_Overriding_Operation (Subp);
+            elsif Must_Override (Spec) then
+               if Is_Overriding_Operation (Subp) then
+                  Set_Is_Overriding_Operation (Subp);
 
-            elsif not Operator_Matches_Spec (Subp, Subp) then
-               Error_Msg_NE ("subprogram & is not overriding", Spec, Subp);
-            end if;
+               elsif not Can_Override then
+                  Error_Msg_NE ("subprogram & is not overriding", Spec, Subp);
+               end if;
 
-         elsif not Error_Posted (Subp)
-           and then Style_Check
-           and then Operator_Matches_Spec (Subp, Subp)
-             and then
-               not Is_Predefined_File_Name
-                 (Unit_File_Name (Get_Source_Unit (Subp)))
-         then
-            Set_Is_Overriding_Operation (Subp);
+            elsif not Error_Posted (Subp)
+              and then Style_Check
+              and then Can_Override
+              and then
+                not Is_Predefined_File_Name
+                  (Unit_File_Name (Get_Source_Unit (Subp)))
+            then
+               Set_Is_Overriding_Operation (Subp);
 
-            --  If style checks are enabled, indicate that the indicator is
-            --  missing. However, at the point of declaration, the type of
-            --  which this is a primitive operation may be private, in which
-            --  case the indicator would be premature.
+               --  If style checks are enabled, indicate that the indicator is
+               --  missing. However, at the point of declaration, the type of
+               --  which this is a primitive operation may be private, in which
+               --  case the indicator would be premature.
 
-            if Has_Private_Declaration (Etype (Subp))
-              or else Has_Private_Declaration (Etype (First_Formal (Subp)))
-            then
-               null;
-            else
-               Style.Missing_Overriding (Decl, Subp);
+               if Has_Private_Declaration (Etype (Subp))
+                 or else Has_Private_Declaration (Etype (First_Formal (Subp)))
+               then
+                  null;
+               else
+                  Style.Missing_Overriding (Decl, Subp);
+               end if;
             end if;
-         end if;
+         end;
 
       elsif Must_Override (Spec) then
          if Ekind (Subp) = E_Entry then
-- 
GitLab