From 7e4f00b47ce58c7a04810c419ff9a70e7bf99186 Mon Sep 17 00:00:00 2001
From: Arnaud Charlet <charlet@gcc.gnu.org>
Date: Thu, 20 Nov 2014 16:13:59 +0100
Subject: [PATCH] [multiple changes]

2014-11-20  Arnaud Charlet  <charlet@adacore.com>

	* s-taspri-solaris.ads: Replace 64 by long_long_integer'size.

2014-11-20  Olivier Hainque  <hainque@adacore.com>

	* init.c (__gnat_map_signal for VxWorks): Use a common mapping
	scheme for VxWorks version >= 6, instead of falling back to the
	vx5 scheme for versions > 6.

2014-11-20  Ed Schonberg  <schonberg@adacore.com>

	* exp_strm.adb (Build_Mutable_Record_Read_Procedure): Use
	base type when constructing subtype indication for constrained
	target object.

2014-11-20  Jose Ruiz  <ruiz@adacore.com>

	* projects.texi: Minor spelling fix.

2014-11-20  Bob Duff  <duff@adacore.com>

	* gnat_ugn.texi: Add doc for --split-line-before-op switch in gnatpp.

2014-11-20  Vincent Celier  <celier@adacore.com>

	* prj-attr.adb (Register_New_Package): Allow the registration
	of an already unknown package and make it known.

From-SVN: r217873
---
 gcc/ada/ChangeLog            | 29 +++++++++++++++++++++++++++++
 gcc/ada/exp_strm.adb         |  2 +-
 gcc/ada/gnat_ugn.texi        |  6 ++++++
 gcc/ada/init.c               |  2 +-
 gcc/ada/prj-attr.adb         | 27 +++++++++++++++++++--------
 gcc/ada/projects.texi        |  2 +-
 gcc/ada/s-taspri-solaris.ads |  2 +-
 7 files changed, 58 insertions(+), 12 deletions(-)

diff --git a/gcc/ada/ChangeLog b/gcc/ada/ChangeLog
index fa056d3bb992..7065302d18ba 100644
--- a/gcc/ada/ChangeLog
+++ b/gcc/ada/ChangeLog
@@ -1,3 +1,32 @@
+2014-11-20  Arnaud Charlet  <charlet@adacore.com>
+
+	* s-taspri-solaris.ads: Replace 64 by long_long_integer'size.
+
+2014-11-20  Olivier Hainque  <hainque@adacore.com>
+
+	* init.c (__gnat_map_signal for VxWorks): Use a common mapping
+	scheme for VxWorks version >= 6, instead of falling back to the
+	vx5 scheme for versions > 6.
+
+2014-11-20  Ed Schonberg  <schonberg@adacore.com>
+
+	* exp_strm.adb (Build_Mutable_Record_Read_Procedure): Use
+	base type when constructing subtype indication for constrained
+	target object.
+
+2014-11-20  Jose Ruiz  <ruiz@adacore.com>
+
+	* projects.texi: Minor spelling fix.
+
+2014-11-20  Bob Duff  <duff@adacore.com>
+
+	* gnat_ugn.texi: Add doc for --split-line-before-op switch in gnatpp.
+
+2014-11-20  Vincent Celier  <celier@adacore.com>
+
+	* prj-attr.adb (Register_New_Package): Allow the registration
+	of an already unknown package and make it known.
+
 2014-11-20  Trevor Saunders  <tsaunders@mozilla.com>
 
 	* gcc-interface/decl.c, gcc-interface/utils.c: replace htab with
diff --git a/gcc/ada/exp_strm.adb b/gcc/ada/exp_strm.adb
index ba0447f28200..210183d8130c 100644
--- a/gcc/ada/exp_strm.adb
+++ b/gcc/ada/exp_strm.adb
@@ -978,7 +978,7 @@ package body Exp_Strm is
           Defining_Identifier => Tmp,
           Object_Definition   =>
             Make_Subtype_Indication (Loc,
-              Subtype_Mark => New_Occurrence_Of (Typ, Loc),
+              Subtype_Mark => New_Occurrence_Of (Base_Type (Typ), Loc),
               Constraint =>
                 Make_Index_Or_Discriminant_Constraint (Loc,
                   Constraints => Cstr))));
diff --git a/gcc/ada/gnat_ugn.texi b/gcc/ada/gnat_ugn.texi
index 9d8a5ee52f78..8f0e5d50ea94 100644
--- a/gcc/ada/gnat_ugn.texi
+++ b/gcc/ada/gnat_ugn.texi
@@ -13970,6 +13970,12 @@ Same as @code{--decimal-grouping}, but for based literals. For
 example, with @code{--based-grouping=4}, @code{16#0001FFFE#} will be
 changed to @code{16#0001_FFFE#}.
 
+@item --split-line-before-op
+@cindex @option{--split-line-before-op} (@command{gnatpp})
+If it is necessary to split a line at a binary operator, by default
+the line is split after the operator. With this option, it is split
+before the operator.
+
 @item --RM-style-spacing
 @cindex @option{--RM-style-spacing} (@command{gnatpp})
 Do not insert an extra blank before various occurrences of
diff --git a/gcc/ada/init.c b/gcc/ada/init.c
index 8a33966d62ba..30f2da4462b9 100644
--- a/gcc/ada/init.c
+++ b/gcc/ada/init.c
@@ -1800,7 +1800,7 @@ __gnat_map_signal (int sig, siginfo_t *si ATTRIBUTE_UNUSED,
       msg = "SIGBUS: possible stack overflow";
       break;
 #endif
-#elif (_WRS_VXWORKS_MAJOR == 6)
+#elif (_WRS_VXWORKS_MAJOR >= 6)
     case SIGILL:
       exception = &constraint_error;
       msg = "SIGILL";
diff --git a/gcc/ada/prj-attr.adb b/gcc/ada/prj-attr.adb
index e356e72d2953..7fb5e92ec297 100644
--- a/gcc/ada/prj-attr.adb
+++ b/gcc/ada/prj-attr.adb
@@ -905,6 +905,7 @@ package body Prj.Attr is
 
    procedure Register_New_Package (Name : String; Id : out Package_Node_Id) is
       Pkg_Name : Name_Id;
+      Found    : Boolean := False;
 
    begin
       if Name'Length = 0 then
@@ -917,17 +918,27 @@ package body Prj.Attr is
 
       for Index in Package_Attributes.First .. Package_Attributes.Last loop
          if Package_Attributes.Table (Index).Name = Pkg_Name then
-            Fail ("cannot register a package with a non unique name """
-                  & Name
-                  & """");
-            Id := Empty_Package;
-            return;
+            if Package_Attributes.Table (Index).Known then
+               Fail ("cannot register a package with a non unique name """
+                     & Name
+                     & """");
+               Id := Empty_Package;
+               return;
+
+            else
+               Found := True;
+               Id := (Value => Index);
+               exit;
+            end if;
          end if;
       end loop;
 
-      Package_Attributes.Increment_Last;
-      Id := (Value => Package_Attributes.Last);
-      Package_Attributes.Table (Package_Attributes.Last) :=
+      if not Found then
+         Package_Attributes.Increment_Last;
+         Id := (Value => Package_Attributes.Last);
+      end if;
+
+      Package_Attributes.Table (Id.Value) :=
         (Name             => Pkg_Name,
          Known            => True,
          First_Attribute  => Empty_Attr);
diff --git a/gcc/ada/projects.texi b/gcc/ada/projects.texi
index da9511bff844..5ff2abc89c07 100644
--- a/gcc/ada/projects.texi
+++ b/gcc/ada/projects.texi
@@ -2643,7 +2643,7 @@ themselves (so for instance you cannot use it to change the value
 of your PATH as seen from the spawned compiler).
 
 This attribute affects the external values as seen in the rest of
-the aggreate projects, and in the aggregated projects.
+the aggregate project, and in the aggregated projects.
 
 The exact value of external a variable comes from one of three
 sources (each level overrides the previous levels):
diff --git a/gcc/ada/s-taspri-solaris.ads b/gcc/ada/s-taspri-solaris.ads
index 1d5c7dba8389..93c520da02a6 100644
--- a/gcc/ada/s-taspri-solaris.ads
+++ b/gcc/ada/s-taspri-solaris.ads
@@ -78,7 +78,7 @@ package System.Task_Primitives is
 
 private
 
-   type Private_Task_Serial_Number is mod 2 ** 64;
+   type Private_Task_Serial_Number is mod 2 ** Long_Long_Integer'Size;
    --  Used to give each task a unique serial number
 
    type Base_Lock is new System.OS_Interface.mutex_t;
-- 
GitLab