From 6f5add73cd2e49d770b4ff4255f06381e8cfd6cb Mon Sep 17 00:00:00 2001
From: Arnaud Charlet <charlet@gcc.gnu.org>
Date: Tue, 27 Sep 2011 11:48:14 +0200
Subject: [PATCH] [multiple changes]

2011-09-27  Pascal Obry  <obry@adacore.com>

	* s-osinte-hpux.ads, s-osinte-aix.ads, s-osinte-solaris-posix.ads,
	s-osinte-irix.ads, s-osinte-darwin.ads, s-osinte-freebsd.ads:
	Add dummy definitions for pthread_rwlock_t
	and pthread_rwlockattr_t on all POSIX platforms.
	* s-taprop-irix.adb, s-taprop-posix.adb (Initialize_Lock): Fix lock
	reference.
	(Finalize_Lock): Likewise.
	(Write_Lock): Likewise.
	(Unlock): Likewise.

2011-09-27  Tristan Gingold  <gingold@adacore.com>

	* s-tassta.adb (Task_Wrapper): Increase Guard_Page_Size value for
	windows 64.

From-SVN: r179254
---
 gcc/ada/ChangeLog                  | 17 +++++++++++++++++
 gcc/ada/s-osinte-aix.ads           |  8 ++++++++
 gcc/ada/s-osinte-darwin.ads        |  8 ++++++++
 gcc/ada/s-osinte-freebsd.ads       |  8 ++++++++
 gcc/ada/s-osinte-hpux.ads          |  8 ++++++++
 gcc/ada/s-osinte-irix.ads          |  8 ++++++++
 gcc/ada/s-osinte-solaris-posix.ads |  8 ++++++++
 gcc/ada/s-taprop-irix.adb          |  8 ++++----
 gcc/ada/s-taprop-posix.adb         |  8 ++++----
 gcc/ada/s-tassta.adb               |  2 +-
 10 files changed, 74 insertions(+), 9 deletions(-)

diff --git a/gcc/ada/ChangeLog b/gcc/ada/ChangeLog
index 4f496a84065a..51e8176bda3d 100644
--- a/gcc/ada/ChangeLog
+++ b/gcc/ada/ChangeLog
@@ -1,3 +1,20 @@
+2011-09-27  Pascal Obry  <obry@adacore.com>
+
+	* s-osinte-hpux.ads, s-osinte-aix.ads, s-osinte-solaris-posix.ads,
+	s-osinte-irix.ads, s-osinte-darwin.ads, s-osinte-freebsd.ads:
+	Add dummy definitions for pthread_rwlock_t
+	and pthread_rwlockattr_t on all POSIX platforms.
+	* s-taprop-irix.adb, s-taprop-posix.adb (Initialize_Lock): Fix lock
+	reference.
+	(Finalize_Lock): Likewise.
+	(Write_Lock): Likewise.
+	(Unlock): Likewise.
+
+2011-09-27  Tristan Gingold  <gingold@adacore.com>
+
+	* s-tassta.adb (Task_Wrapper): Increase Guard_Page_Size value for
+	windows 64.
+
 2011-09-27  Pascal Obry  <obry@adacore.com>
 
 	* s-osinte-hpux.ads, s-taprop-vxworks.adb, s-taspri-vxworks.ads,
diff --git a/gcc/ada/s-osinte-aix.ads b/gcc/ada/s-osinte-aix.ads
index 586d42f8f0a7..c8e660826042 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 2bd15a8b211a..fe2a10a33152 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 5c46c29b983a..d3d5c8763e41 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 716d821654a0..bc9a7091d6fb 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 fb1bbb5c55cf..ddeadcb61476 100644
--- a/gcc/ada/s-osinte-irix.ads
+++ b/gcc/ada/s-osinte-irix.ads
@@ -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-solaris-posix.ads b/gcc/ada/s-osinte-solaris-posix.ads
index 6c266f9babfb..8781a12dd678 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-taprop-irix.adb b/gcc/ada/s-taprop-irix.adb
index 264690499203..5b4d4bef16e4 100644
--- a/gcc/ada/s-taprop-irix.adb
+++ b/gcc/ada/s-taprop-irix.adb
@@ -255,7 +255,7 @@ package body System.Task_Primitives.Operations is
          pragma Assert (Result = 0);
       end if;
 
-      Result := pthread_mutex_init (L, Attributes'Access);
+      Result := pthread_mutex_init (L.WO'Access, Attributes'Access);
       pragma Assert (Result = 0 or else Result = ENOMEM);
 
       if Result = ENOMEM then
@@ -314,7 +314,7 @@ package body System.Task_Primitives.Operations is
    procedure Finalize_Lock (L : not null access Lock) is
       Result : Interfaces.C.int;
    begin
-      Result := pthread_mutex_destroy (L);
+      Result := pthread_mutex_destroy (L.WO'Access);
       pragma Assert (Result = 0);
    end Finalize_Lock;
 
@@ -335,7 +335,7 @@ package body System.Task_Primitives.Operations is
       Result : Interfaces.C.int;
 
    begin
-      Result := pthread_mutex_lock (L);
+      Result := pthread_mutex_lock (L.WO'Access);
       Ceiling_Violation := Result = EINVAL;
 
       --  Assumes the cause of EINVAL is a priority ceiling violation
@@ -381,7 +381,7 @@ package body System.Task_Primitives.Operations is
    procedure Unlock (L : not null access Lock) is
       Result : Interfaces.C.int;
    begin
-      Result := pthread_mutex_unlock (L);
+      Result := pthread_mutex_unlock (L.WO'Access);
       pragma Assert (Result = 0);
    end Unlock;
 
diff --git a/gcc/ada/s-taprop-posix.adb b/gcc/ada/s-taprop-posix.adb
index af0a597e5fc3..1dec99966eef 100644
--- a/gcc/ada/s-taprop-posix.adb
+++ b/gcc/ada/s-taprop-posix.adb
@@ -310,7 +310,7 @@ package body System.Task_Primitives.Operations is
          pragma Assert (Result = 0);
       end if;
 
-      Result := pthread_mutex_init (L, Attributes'Access);
+      Result := pthread_mutex_init (L.WO'Access, Attributes'Access);
       pragma Assert (Result = 0 or else Result = ENOMEM);
 
       if Result = ENOMEM then
@@ -372,7 +372,7 @@ package body System.Task_Primitives.Operations is
    procedure Finalize_Lock (L : not null access Lock) is
       Result : Interfaces.C.int;
    begin
-      Result := pthread_mutex_destroy (L);
+      Result := pthread_mutex_destroy (L.WO'Access);
       pragma Assert (Result = 0);
    end Finalize_Lock;
 
@@ -393,7 +393,7 @@ package body System.Task_Primitives.Operations is
       Result : Interfaces.C.int;
 
    begin
-      Result := pthread_mutex_lock (L);
+      Result := pthread_mutex_lock (L.WO'Access);
 
       --  Assume that the cause of EINVAL is a priority ceiling violation
 
@@ -439,7 +439,7 @@ package body System.Task_Primitives.Operations is
    procedure Unlock (L : not null access Lock) is
       Result : Interfaces.C.int;
    begin
-      Result := pthread_mutex_unlock (L);
+      Result := pthread_mutex_unlock (L.WO'Access);
       pragma Assert (Result = 0);
    end Unlock;
 
diff --git a/gcc/ada/s-tassta.adb b/gcc/ada/s-tassta.adb
index 6449bf6b0171..27c847df6e9a 100644
--- a/gcc/ada/s-tassta.adb
+++ b/gcc/ada/s-tassta.adb
@@ -1164,7 +1164,7 @@ package body System.Tasking.Stages is
 
       if System.Stack_Usage.Is_Enabled then
          declare
-            Guard_Page_Size : constant := 12 * 1024;
+            Guard_Page_Size : constant := 16 * 1024;
             --  Part of the stack used as a guard page. This is an OS dependent
             --  value, so we need to use the maximum. This value is only used
             --  when the stack address is known, that is currently Windows.
-- 
GitLab