diff --git a/gcc/ada/ChangeLog b/gcc/ada/ChangeLog
index 3ef5e6df5e060e1c9d49f3dd7a1ac4f8e360855a..1e4d3db4f9530772025e5916f6edaa1ae52d1a85 100644
--- a/gcc/ada/ChangeLog
+++ b/gcc/ada/ChangeLog
@@ -1,7 +1,17 @@
+2009-09-17  Bob Duff  <duff@adacore.com>
+
+	* g-socket.ads: Document the fact that Close_Selector has no effect on
+	a closed selector.
+	* g-socket.adb: Raise an exception when a Selector that should be open
+	is closed.
+	(Check_Selector): Declare RSig as a constant rather than a renames,
+	less confusing.
+
 2009-09-17  Robert Dewar  <dewar@adacore.com>
 
 	* exp_ch9.adb, exp_ch5.adb, exp_ch4.adb, prj-conf.adb, prj-env.ads,
-	prj-ext.adb: Minor reformatting
+	prj-ext.adb, prj-ext.ads, prj-pars.adb, prj-part.adb, prj-proc.adb,
+	prj-tree.ads: Minor reformatting
 
 2009-09-17  Emmanuel Briot  <briot@adacore.com>
 
diff --git a/gcc/ada/g-socket.adb b/gcc/ada/g-socket.adb
index d32ebfc37a84395dac184c11baf0b24ccc660d7d..8afde3beec3cb90a070d4851edbb4a853c56c253 100644
--- a/gcc/ada/g-socket.adb
+++ b/gcc/ada/g-socket.adb
@@ -282,6 +282,12 @@ package body GNAT.Sockets is
       Res : C.int;
 
    begin
+      if Selector.R_Sig_Socket = No_Socket
+        or else Selector.W_Sig_Socket = No_Socket
+      then
+         raise Program_Error with "closed selector";
+      end if;
+
       --  Send one byte to unblock select system call
 
       Res := Signalling_Fds.Write (C.int (Selector.W_Sig_Socket));
@@ -330,6 +336,14 @@ package body GNAT.Sockets is
       Status   : out Selector_Status)
    is
    begin
+      if Selector /= null
+        and then (Selector.R_Sig_Socket = No_Socket
+                    or else
+                  Selector.W_Sig_Socket = No_Socket)
+      then
+         raise Program_Error with "closed selector";
+      end if;
+
       --  Wait for socket to become available for reading
 
       Wait_On_Socket
@@ -473,11 +487,17 @@ package body GNAT.Sockets is
    is
       Res  : C.int;
       Last : C.int;
-      RSig : Socket_Type renames Selector.R_Sig_Socket;
+      RSig : constant Socket_Type := Selector.R_Sig_Socket;
       TVal : aliased Timeval;
       TPtr : Timeval_Access;
 
    begin
+      if Selector.R_Sig_Socket = No_Socket
+        or else Selector.W_Sig_Socket = No_Socket
+      then
+         raise Program_Error with "closed selector";
+      end if;
+
       Status := Completed;
 
       --  No timeout or Forever is indicated by a null timeval pointer
@@ -563,6 +583,12 @@ package body GNAT.Sockets is
 
    procedure Close_Selector (Selector : in out Selector_Type) is
    begin
+      if Selector.R_Sig_Socket = No_Socket
+        or else Selector.W_Sig_Socket = No_Socket
+      then
+         return;
+      end if;
+
       --  Close the signalling file descriptors used internally for the
       --  implementation of Abort_Selector.
 
@@ -636,6 +662,13 @@ package body GNAT.Sockets is
       --  Used to set Socket to non-blocking I/O
 
    begin
+      if Selector /= null and then
+        (Selector.R_Sig_Socket = No_Socket
+           or else Selector.W_Sig_Socket = No_Socket)
+      then
+         raise Program_Error with "closed selector";
+      end if;
+
       --  Set the socket to non-blocking I/O
 
       Req := (Name => Non_Blocking_IO, Enabled => True);
@@ -727,6 +760,12 @@ package body GNAT.Sockets is
       Res     : C.int;
 
    begin
+      if Selector.R_Sig_Socket /= No_Socket
+        or else Selector.W_Sig_Socket /= No_Socket
+      then
+         raise Program_Error with "selector already open";
+      end if;
+
       --  We open two signalling file descriptors. One of them is used to send
       --  data to the other, which is included in a C_Select socket set. The
       --  communication is used to force a call to C_Select to complete, and
diff --git a/gcc/ada/g-socket.ads b/gcc/ada/g-socket.ads
index a6445e044ad0424217a42cf106f1c837c8a36cb1..39a917a548025ca461214414bd8638b29715dcb5 100644
--- a/gcc/ada/g-socket.ads
+++ b/gcc/ada/g-socket.ads
@@ -1072,7 +1072,8 @@ package GNAT.Sockets is
    --  Close Selector and all internal descriptors associated; deallocate any
    --  associated resources. This subprogram may be called only when there is
    --  no other task still using Selector (i.e. still executing Check_Selector
-   --  or Abort_Selector on this Selector).
+   --  or Abort_Selector on this Selector). Has no effect if Selector is
+   --  already closed.
 
    procedure Check_Selector
      (Selector     : in out Selector_Type;