diff --git a/gcc/ada/ChangeLog b/gcc/ada/ChangeLog
index 8d34c2e1a7fca7a9b5080250e2f34a76993f55e7..d200d17662c4a49c2e8b96dc772277336ef572da 100644
--- a/gcc/ada/ChangeLog
+++ b/gcc/ada/ChangeLog
@@ -1,3 +1,20 @@
+2011-09-27  Pascal Obry  <obry@adacore.com>
+
+	* exp_ch9.adb, s-taspri-posix.ads: Minor reformatting.
+
+2011-09-27  Pascal Obry  <obry@adacore.com>
+
+	* s-osinte-aix.ads, s-osinte-darwin.ads, s-osinte-freebsd.ads,
+	s-osinte-hpux.ads, s-osinte-irix.ads,
+	s-osinte-solaris-posix.ads (pthread_rwlock_t): New definition alias of
+	pthread_mutex_t.
+	(pthread_rwlockattr_t): New definition alias of pthread_mutexattr_t.
+	* s-osinte-linux.ads (pthread_rwlock_t, pthread_rwlockattr_t,
+	pthread_rwlockattr_init, pthread_rwlockattr_destroy,
+	pthread_rwlockattr_setkind_np, pthread_rwlock_init,
+	pthread_rwlock_destroy, pthread_rwlock_rdlock,
+	pthread_rwlock_wrlock, pthread_rwlock_unlock): New.
+
 2011-09-27  Pascal Obry  <obry@adacore.com>
 
 	* rtsfind.ads: Add RE_Lock_Read_Only into rtsfind circuitry.
diff --git a/gcc/ada/exp_ch9.adb b/gcc/ada/exp_ch9.adb
index 2a8a46481cb57b578ef87cb8d9998a159f4c85b5..b8bcfaedc316cfbdf9c8481433dd3aa48d186522 100644
--- a/gcc/ada/exp_ch9.adb
+++ b/gcc/ada/exp_ch9.adb
@@ -1690,7 +1690,7 @@ package body Exp_Ch9 is
       --  The parameter that designates the synchronized object in the call
 
       Actuals : constant List_Id := New_List;
-      --  the actuals in the entry call.
+      --  the actuals in the entry call
 
       Decls : constant List_Id := New_List;
 
@@ -3008,7 +3008,7 @@ package body Exp_Ch9 is
                raise Program_Error;
          end case;
 
-         --  Establish link between subprogram body entity and source entry.
+         --  Establish link between subprogram body entity and source entry
 
          Set_Corresponding_Protected_Entry (Edef, Ent);
 
@@ -8337,7 +8337,7 @@ package body Exp_Ch9 is
             Insert_After (Current_Node, Sub);
             Analyze (Sub);
 
-            --  build wrapper procedure for pre/postconditions.
+            --  build wrapper procedure for pre/postconditions
 
             Build_PPC_Wrapper (Comp_Id, N);
 
@@ -10615,10 +10615,12 @@ package body Exp_Ch9 is
         Make_Defining_Identifier (Sloc (Tasktyp),
           Chars => New_External_Name (Tasknm, 'Z')));
 
-      if Present (Taskdef) and then Has_Storage_Size_Pragma (Taskdef) and then
-        Is_Static_Expression (Expression (First (
-          Pragma_Argument_Associations (Find_Task_Or_Protected_Pragma (
-            Taskdef, Name_Storage_Size)))))
+      if Present (Taskdef)
+        and then Has_Storage_Size_Pragma (Taskdef)
+        and then
+          Is_Static_Expression (Expression (First (
+            Pragma_Argument_Associations (Find_Task_Or_Protected_Pragma (
+              Taskdef, Name_Storage_Size)))))
       then
          Size_Decl :=
            Make_Object_Declaration (Loc,
diff --git a/gcc/ada/s-osinte-aix.ads b/gcc/ada/s-osinte-aix.ads
index 586d42f8f0a799b14996b2aa21aad5a20667bc5d..c8e660826042b503f4e0eaa241a74f22d48d7072 100644
--- a/gcc/ada/s-osinte-aix.ads
+++ b/gcc/ada/s-osinte-aix.ads
@@ -276,6 +276,14 @@ package System.OS_Interface is
    PTHREAD_SCOPE_PROCESS : constant := 1;
    PTHREAD_SCOPE_SYSTEM  : constant := 0;
 
+   --  Read/Write lock not supported on AIX. To add support both types
+   --  pthread_rwlock_t and pthread_rwlockattr_t must properly be defined
+   --  with the associated routines pthread_rwlock_[init/destroy] and
+   --  pthread_rwlock_[rdlock/wrlock/unlock].
+
+   subtype pthread_rwlock_t     is pthread_mutex_t;
+   subtype pthread_rwlockattr_t is pthread_mutexattr_t;
+
    -----------
    -- Stack --
    -----------
diff --git a/gcc/ada/s-osinte-darwin.ads b/gcc/ada/s-osinte-darwin.ads
index 2bd15a8b211abc3e6b910bcd771c6b8629f32108..fe2a10a33152b872ba602bb3efaec3cc9b871232 100644
--- a/gcc/ada/s-osinte-darwin.ads
+++ b/gcc/ada/s-osinte-darwin.ads
@@ -256,6 +256,14 @@ package System.OS_Interface is
    PTHREAD_SCOPE_PROCESS : constant := 2;
    PTHREAD_SCOPE_SYSTEM  : constant := 1;
 
+   --  Read/Write lock not supported on Darwin. To add support both types
+   --  pthread_rwlock_t and pthread_rwlockattr_t must properly be defined
+   --  with the associated routines pthread_rwlock_[init/destroy] and
+   --  pthread_rwlock_[rdlock/wrlock/unlock].
+
+   subtype pthread_rwlock_t     is pthread_mutex_t;
+   subtype pthread_rwlockattr_t is pthread_mutexattr_t;
+
    -----------
    -- Stack --
    -----------
diff --git a/gcc/ada/s-osinte-freebsd.ads b/gcc/ada/s-osinte-freebsd.ads
index 5c46c29b983a0f8895170b2314d08f824b97ec74..d3d5c8763e410bfd814a404759a5d42f98732d5e 100644
--- a/gcc/ada/s-osinte-freebsd.ads
+++ b/gcc/ada/s-osinte-freebsd.ads
@@ -289,6 +289,14 @@ package System.OS_Interface is
    PTHREAD_SCOPE_PROCESS : constant := 0;
    PTHREAD_SCOPE_SYSTEM  : constant := 2;
 
+   --  Read/Write lock not supported on freebsd. To add support both types
+   --  pthread_rwlock_t and pthread_rwlockattr_t must properly be defined
+   --  with the associated routines pthread_rwlock_[init/destroy] and
+   --  pthread_rwlock_[rdlock/wrlock/unlock].
+
+   subtype pthread_rwlock_t     is pthread_mutex_t;
+   subtype pthread_rwlockattr_t is pthread_mutexattr_t;
+
    -----------
    -- Stack --
    -----------
diff --git a/gcc/ada/s-osinte-hpux.ads b/gcc/ada/s-osinte-hpux.ads
index 716d821654a02d8b1aba47bdb25ae7b008a82a37..bc9a7091d6fba4279ad7164d68d3d1a485bb385a 100644
--- a/gcc/ada/s-osinte-hpux.ads
+++ b/gcc/ada/s-osinte-hpux.ads
@@ -265,6 +265,14 @@ package System.OS_Interface is
    PTHREAD_SCOPE_PROCESS : constant := 2;
    PTHREAD_SCOPE_SYSTEM  : constant := 1;
 
+   --  Read/Write lock not supported on HPUX. To add support both types
+   --  pthread_rwlock_t and pthread_rwlockattr_t must properly be defined
+   --  with the associated routines pthread_rwlock_[init/destroy] and
+   --  pthread_rwlock_[rdlock/wrlock/unlock].
+
+   subtype pthread_rwlock_t     is pthread_mutex_t;
+   subtype pthread_rwlockattr_t is pthread_mutexattr_t;
+
    -----------
    -- Stack --
    -----------
diff --git a/gcc/ada/s-osinte-irix.ads b/gcc/ada/s-osinte-irix.ads
index 8af4bd87542c2eeaddcb1164b526d294c924ef57..ddeadcb61476d28242076f2e05b432bee60a6e46 100644
--- a/gcc/ada/s-osinte-irix.ads
+++ b/gcc/ada/s-osinte-irix.ads
@@ -7,7 +7,7 @@
 --                                  S p e c                                 --
 --                                                                          --
 --             Copyright (C) 1991-1994, Florida State University            --
---          Copyright (C) 1995-2010, Free Software Foundation, Inc.         --
+--          Copyright (C) 1995-2011, Free Software Foundation, Inc.         --
 --                                                                          --
 -- GNAT is free software;  you can  redistribute it  and/or modify it under --
 -- terms of the  GNU General Public License as published  by the Free Soft- --
@@ -250,6 +250,14 @@ package System.OS_Interface is
 
    PTHREAD_CREATE_DETACHED : constant := 1;
 
+   --  Read/Write lock not supported on SGI. To add support both types
+   --  pthread_rwlock_t and pthread_rwlockattr_t must properly be defined
+   --  with the associated routines pthread_rwlock_[init/destroy] and
+   --  pthread_rwlock_[rdlock/wrlock/unlock].
+
+   subtype pthread_rwlock_t     is pthread_mutex_t;
+   subtype pthread_rwlockattr_t is pthread_mutexattr_t;
+
    -----------
    -- Stack --
    -----------
diff --git a/gcc/ada/s-osinte-linux.ads b/gcc/ada/s-osinte-linux.ads
index bd37c119fd1bd704b865e6fa3b960aaa1ecd74ca..387486637972bc8f52aaae3ffa130be0a360fd64 100644
--- a/gcc/ada/s-osinte-linux.ads
+++ b/gcc/ada/s-osinte-linux.ads
@@ -272,12 +272,14 @@ package System.OS_Interface is
    function To_pthread_t is
      new Ada.Unchecked_Conversion (unsigned_long, pthread_t);
 
-   type pthread_mutex_t     is limited private;
-   type pthread_cond_t      is limited private;
-   type pthread_attr_t      is limited private;
-   type pthread_mutexattr_t is limited private;
-   type pthread_condattr_t  is limited private;
-   type pthread_key_t       is private;
+   type pthread_mutex_t      is limited private;
+   type pthread_rwlock_t     is limited private;
+   type pthread_cond_t       is limited private;
+   type pthread_attr_t       is limited private;
+   type pthread_mutexattr_t  is limited private;
+   type pthread_rwlockattr_t is limited private;
+   type pthread_condattr_t   is limited private;
+   type pthread_key_t        is private;
 
    PTHREAD_CREATE_DETACHED : constant := 1;
 
@@ -358,6 +360,42 @@ package System.OS_Interface is
    function pthread_mutex_unlock (mutex : access pthread_mutex_t) return int;
    pragma Import (C, pthread_mutex_unlock, "pthread_mutex_unlock");
 
+   function pthread_rwlockattr_init
+     (attr : access pthread_rwlockattr_t) return int;
+   pragma Import (C, pthread_rwlockattr_init, "pthread_rwlockattr_init");
+
+   function pthread_rwlockattr_destroy
+     (attr : access pthread_rwlockattr_t) return int;
+   pragma Import (C, pthread_rwlockattr_destroy, "pthread_rwlockattr_destroy");
+
+   PTHREAD_RWLOCK_PREFER_READER_NP              : constant := 0;
+   PTHREAD_RWLOCK_PREFER_WRITER_NP              : constant := 1;
+   PTHREAD_RWLOCK_PREFER_WRITER_NONRECURSIVE_NP : constant := 2;
+
+   function pthread_rwlockattr_setkind_np
+     (attr : access pthread_rwlockattr_t;
+      pref : int) return int;
+   pragma Import
+     (C, pthread_rwlockattr_setkind_np, "pthread_rwlockattr_setkind_np");
+
+   function pthread_rwlock_init
+     (mutex : access pthread_rwlock_t;
+      attr  : access pthread_rwlockattr_t) return int;
+   pragma Import (C, pthread_rwlock_init, "pthread_rwlock_init");
+
+   function pthread_rwlock_destroy
+     (mutex : access pthread_rwlock_t) return int;
+   pragma Import (C, pthread_rwlock_destroy, "pthread_rwlock_destroy");
+
+   function pthread_rwlock_rdlock (mutex : access pthread_rwlock_t) return int;
+   pragma Import (C, pthread_rwlock_rdlock, "pthread_rwlock_rdlock");
+
+   function pthread_rwlock_wrlock (mutex : access pthread_rwlock_t) return int;
+   pragma Import (C, pthread_rwlock_wrlock, "pthread_rwlock_wrlock");
+
+   function pthread_rwlock_unlock (mutex : access pthread_rwlock_t) return int;
+   pragma Import (C, pthread_rwlock_unlock, "pthread_rwlock_unlock");
+
    function pthread_condattr_init
      (attr : access pthread_condattr_t) return int;
    pragma Import (C, pthread_condattr_init, "pthread_condattr_init");
@@ -588,6 +626,18 @@ private
    pragma Convention (C, pthread_mutex_t);
    for pthread_mutex_t'Alignment use Interfaces.C.unsigned_long'Alignment;
 
+   type pthread_rwlockattr_t is record
+      Data : char_array (1 .. OS_Constants.PTHREAD_RWLOCKATTR_SIZE);
+   end record;
+   pragma Convention (C, pthread_rwlockattr_t);
+   for pthread_rwlockattr_t'Alignment use Interfaces.C.unsigned_long'Alignment;
+
+   type pthread_rwlock_t is record
+      Data : char_array (1 .. OS_Constants.PTHREAD_RWLOCK_SIZE);
+   end record;
+   pragma Convention (C, pthread_rwlock_t);
+   for pthread_rwlock_t'Alignment use Interfaces.C.unsigned_long'Alignment;
+
    type pthread_cond_t is record
       Data : char_array (1 .. OS_Constants.PTHREAD_COND_SIZE);
    end record;
diff --git a/gcc/ada/s-osinte-solaris-posix.ads b/gcc/ada/s-osinte-solaris-posix.ads
index 6c266f9babfb56a56a57b7b3ba415d3d7d18f19d..8781a12dd6782f54b64743c8449729856079960a 100644
--- a/gcc/ada/s-osinte-solaris-posix.ads
+++ b/gcc/ada/s-osinte-solaris-posix.ads
@@ -255,6 +255,14 @@ package System.OS_Interface is
    type pthread_condattr_t  is limited private;
    type pthread_key_t       is private;
 
+   --  Read/Write lock not supported on Solaris. To add support both types
+   --  pthread_rwlock_t and pthread_rwlockattr_t must properly be defined
+   --  with the associated routines pthread_rwlock_[init/destroy] and
+   --  pthread_rwlock_[rdlock/wrlock/unlock].
+
+   subtype pthread_rwlock_t     is pthread_mutex_t;
+   subtype pthread_rwlockattr_t is pthread_mutexattr_t;
+
    PTHREAD_CREATE_DETACHED : constant := 16#40#;
 
    PTHREAD_SCOPE_PROCESS : constant := 0;
diff --git a/gcc/ada/s-taspri-posix.ads b/gcc/ada/s-taspri-posix.ads
index 6a076d35196cf0f1934ac6c99125efc8196a5540..77f6321359b8ba44515f8c57ed28a7accc1b3fd5 100644
--- a/gcc/ada/s-taspri-posix.ads
+++ b/gcc/ada/s-taspri-posix.ads
@@ -1,13 +1,13 @@
 ------------------------------------------------------------------------------
 --                                                                          --
---                  GNAT RUN-TIME LIBRARY (GNARL) COMPONENTS                --
+--                 GNAT RUN-TIME LIBRARY (GNARL) COMPONENTS                 --
 --                                                                          --
---                 S Y S T E M . T A S K _ P R I M I T I V E S              --
+--               S Y S T E M . T A S K _ P R I M I T I V E S                --
 --                                                                          --
---                                  S p e c                                 --
+--                                 S p e c                                  --
 --                                                                          --
---             Copyright (C) 1991-1994, Florida State University            --
---                     Copyright (C) 1995-2010, AdaCore                     --
+--            Copyright (C) 1991-1994, Florida State University             --
+--                     Copyright (C) 1995-2011, AdaCore                     --
 --                                                                          --
 -- 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- --