From c83075965b324e46b3225cac95391aaaa9fe1805 Mon Sep 17 00:00:00 2001
From: Arnaud Charlet <charlet@adacore.com>
Date: Tue, 20 Oct 2015 12:40:36 +0000
Subject: [PATCH] s-valllu.adb, [...]: Fix typos.

2015-10-20  Arnaud Charlet  <charlet@adacore.com>

	* s-valllu.adb, sem_ch3.adb, layout.adb, a-crbtgo.adb, exp_ch9.adb,
	make.adb, g-diopit.adb, s-valuns.adb, sem_ch9.adb, sem_ch10.adb,
	sem_ch12.adb, a-tifiio.adb, g-dynhta.adb, uintp.adb,
	sem_util.adb, sem_res.adb, s-htable.adb, exp_tss.adb, s-soflin.ads,
	exp_ch6.adb, sem_ch6.adb, a-rbtgbo.adb, par-ch12.adb, sem_ch8.adb,
	sem_eval.adb, mdll.adb, par-ch5.adb, s-poosiz.adb, sem_ch4.adb,
	a-ngelfu.adb, s-taspri-solaris.ads, a-cforse.adb: Fix typos.

From-SVN: r229077
---
 gcc/ada/ChangeLog            | 10 ++++++++++
 gcc/ada/a-cforse.adb         |  2 +-
 gcc/ada/a-crbtgo.adb         |  4 ++--
 gcc/ada/a-ngelfu.adb         |  4 ++--
 gcc/ada/a-rbtgbo.adb         |  4 ++--
 gcc/ada/a-tifiio.adb         |  4 ++--
 gcc/ada/exp_ch6.adb          |  4 ++--
 gcc/ada/exp_ch9.adb          |  2 +-
 gcc/ada/exp_tss.adb          |  2 +-
 gcc/ada/g-diopit.adb         |  6 +++---
 gcc/ada/g-dynhta.adb         |  4 ++--
 gcc/ada/layout.adb           |  2 +-
 gcc/ada/make.adb             |  2 +-
 gcc/ada/mdll.adb             |  4 ++--
 gcc/ada/par-ch12.adb         |  2 +-
 gcc/ada/par-ch5.adb          |  4 ++--
 gcc/ada/s-htable.adb         |  4 ++--
 gcc/ada/s-poosiz.adb         |  4 ++--
 gcc/ada/s-soflin.ads         |  6 +++---
 gcc/ada/s-taspri-solaris.ads |  4 ++--
 gcc/ada/s-valllu.adb         |  4 ++--
 gcc/ada/s-valuns.adb         |  4 ++--
 gcc/ada/sem_ch10.adb         |  2 +-
 gcc/ada/sem_ch12.adb         |  8 ++++----
 gcc/ada/sem_ch3.adb          |  6 +++---
 gcc/ada/sem_ch4.adb          |  2 +-
 gcc/ada/sem_ch6.adb          |  2 +-
 gcc/ada/sem_ch8.adb          |  2 +-
 gcc/ada/sem_ch9.adb          |  2 +-
 gcc/ada/sem_eval.adb         |  2 +-
 gcc/ada/sem_res.adb          |  6 +++---
 gcc/ada/sem_util.adb         |  4 ++--
 gcc/ada/uintp.adb            |  4 ++--
 33 files changed, 68 insertions(+), 58 deletions(-)

diff --git a/gcc/ada/ChangeLog b/gcc/ada/ChangeLog
index acfc2e481035..3e0d760a6597 100644
--- a/gcc/ada/ChangeLog
+++ b/gcc/ada/ChangeLog
@@ -1,3 +1,13 @@
+2015-10-20  Arnaud Charlet  <charlet@adacore.com>
+
+	* s-valllu.adb, sem_ch3.adb, layout.adb, a-crbtgo.adb, exp_ch9.adb,
+	make.adb, g-diopit.adb, s-valuns.adb, sem_ch9.adb, sem_ch10.adb,
+	sem_ch12.adb, a-tifiio.adb, g-dynhta.adb, uintp.adb,
+	sem_util.adb, sem_res.adb, s-htable.adb, exp_tss.adb, s-soflin.ads,
+	exp_ch6.adb, sem_ch6.adb, a-rbtgbo.adb, par-ch12.adb, sem_ch8.adb,
+	sem_eval.adb, mdll.adb, par-ch5.adb, s-poosiz.adb, sem_ch4.adb,
+	a-ngelfu.adb, s-taspri-solaris.ads, a-cforse.adb: Fix typos.
+
 2015-10-20  Arnaud Charlet  <charlet@adacore.com>
 
 	* sem_aggr.adb, mlib-prj.adb, prep.adb, eval_fat.adb, rtsfind.adb,
diff --git a/gcc/ada/a-cforse.adb b/gcc/ada/a-cforse.adb
index 2b09018ab57e..cf4e2ab1a36a 100644
--- a/gcc/ada/a-cforse.adb
+++ b/gcc/ada/a-cforse.adb
@@ -584,7 +584,7 @@ is
    -------------------
 
    function First_Element (Container : Set) return Element_Type is
-      Fst : constant Count_Type :=  First (Container).Node;
+      Fst : constant Count_Type := First (Container).Node;
    begin
       if Fst = 0 then
          raise Constraint_Error with "set is empty";
diff --git a/gcc/ada/a-crbtgo.adb b/gcc/ada/a-crbtgo.adb
index bfc0bcf3a429..03079618792c 100644
--- a/gcc/ada/a-crbtgo.adb
+++ b/gcc/ada/a-crbtgo.adb
@@ -157,7 +157,7 @@ package body Ada.Containers.Red_Black_Trees.Generic_Operations is
         and then Color (X) = Black
       loop
          if X = Left (Parent (X)) then
-            W :=  Right (Parent (X));
+            W := Right (Parent (X));
 
             if Color (W) = Red then
                Set_Color (W, Black);
@@ -201,7 +201,7 @@ package body Ada.Containers.Red_Black_Trees.Generic_Operations is
          else
             pragma Assert (X = Right (Parent (X)));
 
-            W :=  Left (Parent (X));
+            W := Left (Parent (X));
 
             if Color (W) = Red then
                Set_Color (W, Black);
diff --git a/gcc/ada/a-ngelfu.adb b/gcc/ada/a-ngelfu.adb
index 7546f75ddb12..f17d92497acd 100644
--- a/gcc/ada/a-ngelfu.adb
+++ b/gcc/ada/a-ngelfu.adb
@@ -127,7 +127,7 @@ package body Ada.Numerics.Generic_Elementary_Functions is
                then
                   Int_Part := Integer (Float_Type'Base'Truncation (A_Right));
                   Result := Left ** Int_Part;
-                  Rest :=  A_Right - Float_Type'Base (Int_Part);
+                  Rest := A_Right - Float_Type'Base (Int_Part);
 
                   --  Compute with two leading bits of the mantissa using
                   --  square roots. Bound  to be better than logarithms, and
@@ -148,7 +148,7 @@ package body Ada.Numerics.Generic_Elementary_Functions is
                      Rest := Rest - 0.25;
                   end if;
 
-                  Result :=  Result *
+                  Result := Result *
                     Float_Type'Base (Aux.Pow (Double (Left), Double (Rest)));
 
                   if Right >= 0.0 then
diff --git a/gcc/ada/a-rbtgbo.adb b/gcc/ada/a-rbtgbo.adb
index b75974065d25..0ef7b02dafe5 100644
--- a/gcc/ada/a-rbtgbo.adb
+++ b/gcc/ada/a-rbtgbo.adb
@@ -88,7 +88,7 @@ package body Ada.Containers.Red_Black_Trees.Generic_Bounded_Operations is
       X := Node;
       while X /= Tree.Root and then Color (N (X)) = Black loop
          if X = Left (N (Parent (N (X)))) then
-            W :=  Right (N (Parent (N (X))));
+            W := Right (N (Parent (N (X))));
 
             if Color (N (W)) = Red then
                Set_Color (N (W), Black);
@@ -132,7 +132,7 @@ package body Ada.Containers.Red_Black_Trees.Generic_Bounded_Operations is
          else
             pragma Assert (X = Right (N (Parent (N (X)))));
 
-            W :=  Left (N (Parent (N (X))));
+            W := Left (N (Parent (N (X))));
 
             if Color (N (W)) = Red then
                Set_Color (N (W), Black);
diff --git a/gcc/ada/a-tifiio.adb b/gcc/ada/a-tifiio.adb
index ff4bb2c4e18f..2fd8b5421f2a 100644
--- a/gcc/ada/a-tifiio.adb
+++ b/gcc/ada/a-tifiio.adb
@@ -6,7 +6,7 @@
 --                                                                          --
 --                                 B o d y                                  --
 --                                                                          --
---          Copyright (C) 1992-2012, Free Software Foundation, Inc.         --
+--          Copyright (C) 1992-2015, 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- --
@@ -231,7 +231,7 @@ package body Ada.Text_IO.Fixed_IO is
 
    --  The final expression for D is
 
-   --     D :=  Integer'Max (-18, Integer'Min (Aft, 18 - (Fore - 1)));
+   --     D := Integer'Max (-18, Integer'Min (Aft, 18 - (Fore - 1)));
 
    --  For Y and Z the following expressions can be derived:
 
diff --git a/gcc/ada/exp_ch6.adb b/gcc/ada/exp_ch6.adb
index 792208a3806a..80a7e0d9dde0 100644
--- a/gcc/ada/exp_ch6.adb
+++ b/gcc/ada/exp_ch6.adb
@@ -1266,7 +1266,7 @@ package body Exp_Ch6 is
                   Reset_Analyzed_Flags (Lhs);
 
                else
-                  Lhs :=  New_Occurrence_Of (Var, Loc);
+                  Lhs := New_Occurrence_Of (Var, Loc);
                end if;
 
                Set_Assignment_OK (Lhs);
@@ -5649,7 +5649,7 @@ package body Exp_Ch6 is
 
          declare
             Decls   : List_Id;
-            Obj_Ptr : constant Entity_Id :=  Make_Temporary (Loc, 'T');
+            Obj_Ptr : constant Entity_Id := Make_Temporary (Loc, 'T');
 
          begin
             Decls := New_List (
diff --git a/gcc/ada/exp_ch9.adb b/gcc/ada/exp_ch9.adb
index b0bf000b9361..05b353095533 100644
--- a/gcc/ada/exp_ch9.adb
+++ b/gcc/ada/exp_ch9.adb
@@ -7674,7 +7674,7 @@ package body Exp_Ch9 is
 
          --  Create the inner block to protect the abortable part
 
-         Hdle :=  New_List (Build_Abort_Block_Handler (Loc));
+         Hdle := New_List (Build_Abort_Block_Handler (Loc));
 
          Prepend_To (Astats,
            Make_Procedure_Call_Statement (Loc,
diff --git a/gcc/ada/exp_tss.adb b/gcc/ada/exp_tss.adb
index 94c15dfb2e16..5bcccbb0a590 100644
--- a/gcc/ada/exp_tss.adb
+++ b/gcc/ada/exp_tss.adb
@@ -152,7 +152,7 @@ package body Exp_Tss is
    begin
       loop
          Btyp := Base_Type (Btyp);
-         Proc :=  TSS (Btyp, Nam);
+         Proc := TSS (Btyp, Nam);
 
          exit when Present (Proc)
            or else not Is_Derived_Type (Btyp);
diff --git a/gcc/ada/g-diopit.adb b/gcc/ada/g-diopit.adb
index 3538deb2fff7..dabea22616f7 100644
--- a/gcc/ada/g-diopit.adb
+++ b/gcc/ada/g-diopit.adb
@@ -6,7 +6,7 @@
 --                                                                          --
 --                                 B o d y                                  --
 --                                                                          --
---                     Copyright (C) 2001-2010, AdaCore                     --
+--                     Copyright (C) 2001-2015, 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- --
@@ -221,8 +221,8 @@ package body GNAT.Directory_Operations.Iteration is
             then
                --  Starting with "<drive>:\"
 
-               DS :=  Strings.Fixed.Index
-                        (SP (SP'First + 3 .. SP'Last), Dir_Seps);
+               DS := Strings.Fixed.Index
+                       (SP (SP'First + 3 .. SP'Last), Dir_Seps);
 
                if DS = 0 then
 
diff --git a/gcc/ada/g-dynhta.adb b/gcc/ada/g-dynhta.adb
index 929191d24aa0..449ac17dec44 100644
--- a/gcc/ada/g-dynhta.adb
+++ b/gcc/ada/g-dynhta.adb
@@ -6,7 +6,7 @@
 --                                                                          --
 --                                 B o d y                                  --
 --                                                                          --
---                     Copyright (C) 2002-2014, AdaCore                     --
+--                     Copyright (C) 2002-2015, 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- --
@@ -157,7 +157,7 @@ package body GNAT.Dynamic_HTables is
 
          else
             loop
-               Next_Elmt :=  Next (Elmt);
+               Next_Elmt := Next (Elmt);
 
                if Next_Elmt = Null_Ptr then
                   return;
diff --git a/gcc/ada/layout.adb b/gcc/ada/layout.adb
index ecdbbacd0dbb..c8d7ed7f6c76 100644
--- a/gcc/ada/layout.adb
+++ b/gcc/ada/layout.adb
@@ -2430,7 +2430,7 @@ package body Layout is
       --  represents them the same way.
 
       if Is_Access_Type (E) then
-         Desig_Type :=  Underlying_Type (Designated_Type (E));
+         Desig_Type := Underlying_Type (Designated_Type (E));
 
          --  If we only have a limited view of the type, see whether the
          --  non-limited view is available.
diff --git a/gcc/ada/make.adb b/gcc/ada/make.adb
index 8fbca9df2b82..f3ac043a7ac7 100644
--- a/gcc/ada/make.adb
+++ b/gcc/ada/make.adb
@@ -6953,7 +6953,7 @@ package body Make is
       Get_Name_String (ALI_File);
       Link_Args (1) := new String'(Name_Buffer (1 .. Name_Len));
 
-      Link_Args (2 .. Args'Length + 1) :=  Args;
+      Link_Args (2 .. Args'Length + 1) := Args;
 
       GNAT.OS_Lib.Normalize_Arguments (Link_Args);
 
diff --git a/gcc/ada/mdll.adb b/gcc/ada/mdll.adb
index e6eb5e936a32..03e3573aacaa 100644
--- a/gcc/ada/mdll.adb
+++ b/gcc/ada/mdll.adb
@@ -6,7 +6,7 @@
 --                                                                          --
 --                                 B o d y                                  --
 --                                                                          --
---          Copyright (C) 1992-2007, Free Software Foundation, Inc.         --
+--          Copyright (C) 1992-2015, 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- --
@@ -326,7 +326,7 @@ package body MDLL is
                        Adr_Opt'Unchecked_Access & All_Options;
          begin
             if Map_File then
-               Params :=  Map_Opt'Unchecked_Access & Params;
+               Params := Map_Opt'Unchecked_Access & Params;
             end if;
 
             Utl.Gcc (Output_File => Dll_File,
diff --git a/gcc/ada/par-ch12.adb b/gcc/ada/par-ch12.adb
index a103d96032b3..cd1f91a0788e 100644
--- a/gcc/ada/par-ch12.adb
+++ b/gcc/ada/par-ch12.adb
@@ -726,7 +726,7 @@ package body Ch12 is
 
          when Tok_Not =>
             if P_Null_Exclusion then
-               Typedef_Node :=  P_Access_Type_Definition;
+               Typedef_Node := P_Access_Type_Definition;
                Set_Null_Exclusion_Present (Typedef_Node);
                return Typedef_Node;
 
diff --git a/gcc/ada/par-ch5.adb b/gcc/ada/par-ch5.adb
index 7b1bc44f39d9..a7d0e5a3d7be 100644
--- a/gcc/ada/par-ch5.adb
+++ b/gcc/ada/par-ch5.adb
@@ -6,7 +6,7 @@
 --                                                                          --
 --                                 B o d y                                  --
 --                                                                          --
---          Copyright (C) 1992-2014, Free Software Foundation, Inc.         --
+--          Copyright (C) 1992-2015, 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- --
@@ -1729,7 +1729,7 @@ package body Ch5 is
       Node1 : Node_Id;
 
    begin
-      Node1 :=  New_Node (N_Iterator_Specification, Sloc (Def_Id));
+      Node1 := New_Node (N_Iterator_Specification, Sloc (Def_Id));
       Set_Defining_Identifier (Node1, Def_Id);
 
       if Token = Tok_Colon then
diff --git a/gcc/ada/s-htable.adb b/gcc/ada/s-htable.adb
index 533027394574..2d6a3c6f477a 100644
--- a/gcc/ada/s-htable.adb
+++ b/gcc/ada/s-htable.adb
@@ -6,7 +6,7 @@
 --                                                                          --
 --                                 B o d y                                  --
 --                                                                          --
---                    Copyright (C) 1995-2013, AdaCore                      --
+--                    Copyright (C) 1995-2015, 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- --
@@ -149,7 +149,7 @@ package body System.HTable is
 
          else
             loop
-               Next_Elmt :=  Next (Elmt);
+               Next_Elmt := Next (Elmt);
 
                if Next_Elmt = Null_Ptr then
                   return;
diff --git a/gcc/ada/s-poosiz.adb b/gcc/ada/s-poosiz.adb
index c2dd03bf5d42..683f32e315d3 100644
--- a/gcc/ada/s-poosiz.adb
+++ b/gcc/ada/s-poosiz.adb
@@ -6,7 +6,7 @@
 --                                                                          --
 --                                 B o d y                                  --
 --                                                                          --
---          Copyright (C) 1992-2009, Free Software Foundation, Inc.         --
+--          Copyright (C) 1992-2015, 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- --
@@ -51,7 +51,7 @@ package body System.Pool_Size is
    function To_Storage_Count_Access is
      new Ada.Unchecked_Conversion (Address, Storage_Count_Access);
 
-   SC_Size : constant :=  SSE.Storage_Count'Object_Size / System.Storage_Unit;
+   SC_Size : constant := SSE.Storage_Count'Object_Size / System.Storage_Unit;
 
    package Variable_Size_Management is
 
diff --git a/gcc/ada/s-soflin.ads b/gcc/ada/s-soflin.ads
index cba89366014b..35dc9628b980 100644
--- a/gcc/ada/s-soflin.ads
+++ b/gcc/ada/s-soflin.ads
@@ -254,9 +254,9 @@ package System.Soft_Links is
    procedure Enter_Master_NT;
    procedure Complete_Master_NT;
 
-   Current_Master  : Get_Integer_Call :=  Current_Master_NT'Access;
-   Enter_Master    : No_Param_Proc    :=  Enter_Master_NT'Access;
-   Complete_Master : No_Param_Proc    :=  Complete_Master_NT'Access;
+   Current_Master  : Get_Integer_Call := Current_Master_NT'Access;
+   Enter_Master    : No_Param_Proc    := Enter_Master_NT'Access;
+   Complete_Master : No_Param_Proc    := Complete_Master_NT'Access;
 
    ----------------------
    -- Delay Soft-Links --
diff --git a/gcc/ada/s-taspri-solaris.ads b/gcc/ada/s-taspri-solaris.ads
index 93c520da02a6..e06d4d4dbbeb 100644
--- a/gcc/ada/s-taspri-solaris.ads
+++ b/gcc/ada/s-taspri-solaris.ads
@@ -6,7 +6,7 @@
 --                                                                          --
 --                                  S p e c                                 --
 --                                                                          --
---          Copyright (C) 1992-2014, Free Software Foundation, Inc.         --
+--          Copyright (C) 1992-2015, Free Software Foundation, Inc.         --
 --                                                                          --
 -- GNARL 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- --
@@ -94,7 +94,7 @@ private
    type Lock is record
       L              : aliased Base_Lock;
       Ceiling        : System.Any_Priority := System.Any_Priority'First;
-      Saved_Priority : System.Any_Priority :=  System.Any_Priority'First;
+      Saved_Priority : System.Any_Priority := System.Any_Priority'First;
       Owner          : Owner_ID;
       Next           : Lock_Ptr;
       Level          : Private_Task_Serial_Number := 0;
diff --git a/gcc/ada/s-valllu.adb b/gcc/ada/s-valllu.adb
index a641be319598..44dbff7c3dff 100644
--- a/gcc/ada/s-valllu.adb
+++ b/gcc/ada/s-valllu.adb
@@ -6,7 +6,7 @@
 --                                                                          --
 --                                 B o d y                                  --
 --                                                                          --
---          Copyright (C) 1992-2014, Free Software Foundation, Inc.         --
+--          Copyright (C) 1992-2015, 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- --
@@ -142,7 +142,7 @@ package body System.Val_LLU is
 
          if Base not in 2 .. 16 then
             Overflow := True;
-            Base :=  16;
+            Base := 16;
          end if;
 
          --  Scan out based integer
diff --git a/gcc/ada/s-valuns.adb b/gcc/ada/s-valuns.adb
index b679807803f7..009d0bc88c1a 100644
--- a/gcc/ada/s-valuns.adb
+++ b/gcc/ada/s-valuns.adb
@@ -6,7 +6,7 @@
 --                                                                          --
 --                                 B o d y                                  --
 --                                                                          --
---          Copyright (C) 1992-2014, Free Software Foundation, Inc.         --
+--          Copyright (C) 1992-2015, 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- --
@@ -142,7 +142,7 @@ package body System.Val_Uns is
 
          if Base not in 2 .. 16 then
             Overflow := True;
-            Base :=  16;
+            Base := 16;
          end if;
 
          --  Scan out based integer
diff --git a/gcc/ada/sem_ch10.adb b/gcc/ada/sem_ch10.adb
index 55456e6996fe..bae9762f7185 100644
--- a/gcc/ada/sem_ch10.adb
+++ b/gcc/ada/sem_ch10.adb
@@ -3127,7 +3127,7 @@ package body Sem_Ch10 is
                --  visible, so analyze the declaration for B now, in case it
                --  has not been done yet.
 
-               Ent :=  Entity (Selector_Name (Nam));
+               Ent := Entity (Selector_Name (Nam));
                Analyze
                  (Parent
                    (Unit_Declaration_Node (Entity (Selector_Name (Nam)))));
diff --git a/gcc/ada/sem_ch12.adb b/gcc/ada/sem_ch12.adb
index da3bd903bd3c..41e90071a4d5 100644
--- a/gcc/ada/sem_ch12.adb
+++ b/gcc/ada/sem_ch12.adb
@@ -1235,7 +1235,7 @@ package body Sem_Ch12 is
 
          elsif No (Selector_Name (Actual)) then
             Found_Assoc := Actual;
-            Act :=  Explicit_Generic_Actual_Parameter (Actual);
+            Act := Explicit_Generic_Actual_Parameter (Actual);
             Num_Matched := Num_Matched + 1;
             Next (Actual);
 
@@ -1254,7 +1254,7 @@ package body Sem_Ch12 is
                   Set_Etype  (Selector_Name (Actual), Etype (A_F));
                   Generate_Reference (A_F, Selector_Name (Actual));
                   Found_Assoc := Actual;
-                  Act :=  Explicit_Generic_Actual_Parameter (Actual);
+                  Act := Explicit_Generic_Actual_Parameter (Actual);
                   Num_Matched := Num_Matched + 1;
                   exit;
                end if;
@@ -3600,7 +3600,7 @@ package body Sem_Ch12 is
                   New_Copy_Tree (Name (Defining_Unit_Name (N))),
                 Defining_Identifier => Act_Decl_Id);
          else
-            Act_Decl_Name :=  Act_Decl_Id;
+            Act_Decl_Name := Act_Decl_Id;
          end if;
 
       --  Case of instantiation of a formal package
@@ -10882,7 +10882,7 @@ package body Sem_Ch12 is
                 Name => New_Copy_Tree (Name (Defining_Unit_Name (Act_Spec))),
                 Defining_Identifier => Act_Body_Id);
          else
-            Act_Body_Name :=  Act_Body_Id;
+            Act_Body_Name := Act_Body_Id;
          end if;
 
          Set_Defining_Unit_Name (Act_Body, Act_Body_Name);
diff --git a/gcc/ada/sem_ch3.adb b/gcc/ada/sem_ch3.adb
index 22e7cbb9d128..ea1640004ff3 100644
--- a/gcc/ada/sem_ch3.adb
+++ b/gcc/ada/sem_ch3.adb
@@ -5935,7 +5935,7 @@ package body Sem_Ch3 is
 
       if ASIS_Mode then
          declare
-            Typ : constant Entity_Id :=  Make_Temporary (Loc, 'S');
+            Typ : constant Entity_Id := Make_Temporary (Loc, 'S');
 
          begin
             if Nkind (Spec) = N_Access_Function_Definition then
@@ -18369,7 +18369,7 @@ package body Sem_Ch3 is
 
          --  The index is given by a subtype with a range constraint
 
-         T :=  Base_Type (Entity (Subtype_Mark (N)));
+         T := Base_Type (Entity (Subtype_Mark (N)));
 
          if not Is_Discrete_Type (T) then
             Error_Msg_N ("discrete type required for range", N);
@@ -21547,7 +21547,7 @@ package body Sem_Ch3 is
       R      : Node_Id;
       Subt   : Entity_Id)
    is
-      Kind : constant Entity_Kind :=  Ekind (Def_Id);
+      Kind : constant Entity_Kind := Ekind (Def_Id);
 
    begin
       --  Defend against previous error
diff --git a/gcc/ada/sem_ch4.adb b/gcc/ada/sem_ch4.adb
index fe677541eb13..b01640d3dcf3 100644
--- a/gcc/ada/sem_ch4.adb
+++ b/gcc/ada/sem_ch4.adb
@@ -7878,7 +7878,7 @@ package body Sem_Ch4 is
          --  Before analysis, a function call appears as an indexed component
          --  if there are no named associations.
 
-         elsif Nkind (Parent_Node) =  N_Indexed_Component
+         elsif Nkind (Parent_Node) = N_Indexed_Component
            and then N = Prefix (Parent_Node)
          then
             Node_To_Replace := Parent_Node;
diff --git a/gcc/ada/sem_ch6.adb b/gcc/ada/sem_ch6.adb
index 455d7023e896..c03269360bfa 100644
--- a/gcc/ada/sem_ch6.adb
+++ b/gcc/ada/sem_ch6.adb
@@ -10361,7 +10361,7 @@ package body Sem_Ch6 is
             Set_Default_Value (Formal, Expression (Param_Spec));
 
             if Present (Expression (Param_Spec)) then
-               Default :=  Expression (Param_Spec);
+               Default := Expression (Param_Spec);
 
                if Is_Scalar_Type (Etype (Default)) then
                   if Nkind (Parameter_Type (Param_Spec)) /=
diff --git a/gcc/ada/sem_ch8.adb b/gcc/ada/sem_ch8.adb
index 290d933bdf02..18023c152ae2 100644
--- a/gcc/ada/sem_ch8.adb
+++ b/gcc/ada/sem_ch8.adb
@@ -9214,7 +9214,7 @@ package body Sem_Ch8 is
       S : Entity_Id;
    begin
       for J in reverse 1 .. Scope_Stack.Last loop
-         S :=  Scope_Stack.Table (J).Entity;
+         S := Scope_Stack.Table (J).Entity;
          Write_Int (Int (S));
          Write_Str (" === ");
          Write_Name (Chars (S));
diff --git a/gcc/ada/sem_ch9.adb b/gcc/ada/sem_ch9.adb
index 1f00ea776c1a..728d17d5563a 100644
--- a/gcc/ada/sem_ch9.adb
+++ b/gcc/ada/sem_ch9.adb
@@ -781,7 +781,7 @@ package body Sem_Ch9 is
       for J in reverse 0 .. Scope_Stack.Last loop
          Task_Nam := Scope_Stack.Table (J).Entity;
          exit when Ekind (Etype (Task_Nam)) = E_Task_Type;
-         Kind :=  Ekind (Task_Nam);
+         Kind := Ekind (Task_Nam);
 
          if Kind /= E_Block and then Kind /= E_Loop
            and then not Is_Entry (Task_Nam)
diff --git a/gcc/ada/sem_eval.adb b/gcc/ada/sem_eval.adb
index f8420d4ad743..28acbf06b4c1 100644
--- a/gcc/ada/sem_eval.adb
+++ b/gcc/ada/sem_eval.adb
@@ -2220,7 +2220,7 @@ package body Sem_Eval is
          --  case of a concatenation of a series of string literals.
 
          if Nkind (Left_Str) = N_String_Literal then
-            Left_Len :=  String_Length (Strval (Left_Str));
+            Left_Len := String_Length (Strval (Left_Str));
 
             --  If the left operand is the empty string, and the right operand
             --  is a string literal (the case of "" & "..."), the result is the
diff --git a/gcc/ada/sem_res.adb b/gcc/ada/sem_res.adb
index 67278efa4560..a96f1d1657a5 100644
--- a/gcc/ada/sem_res.adb
+++ b/gcc/ada/sem_res.adb
@@ -7395,7 +7395,7 @@ package body Sem_Res is
 
          declare
             Pref : constant Node_Id := Prefix (Entry_Name);
-            Ent  : constant Entity_Id :=  Entity (Selector_Name (Entry_Name));
+            Ent  : constant Entity_Id := Entity (Selector_Name (Entry_Name));
             I    : Interp_Index;
             It   : Interp;
 
@@ -7418,7 +7418,7 @@ package body Sem_Res is
       else pragma Assert (Nkind (Entry_Name) = N_Indexed_Component);
          Nam := Entity (Selector_Name (Prefix (Entry_Name)));
          Resolve (Prefix (Prefix (Entry_Name)));
-         Index :=  First (Expressions (Entry_Name));
+         Index := First (Expressions (Entry_Name));
          Resolve (Index, Entry_Index_Type (Nam));
 
          --  Up to this point the expression could have been the actual in a
@@ -12049,7 +12049,7 @@ package body Sem_Res is
             if Present (It.Typ) then
                N1  := It1.Nam;
                T1  := It1.Typ;
-               It1 :=  Disambiguate (Operand, I1, I, Any_Type);
+               It1 := Disambiguate (Operand, I1, I, Any_Type);
 
                if It1 = No_Interp then
                   Conversion_Error_N
diff --git a/gcc/ada/sem_util.adb b/gcc/ada/sem_util.adb
index 162e2bbfb7ec..152be0282b52 100644
--- a/gcc/ada/sem_util.adb
+++ b/gcc/ada/sem_util.adb
@@ -1129,7 +1129,7 @@ package body Sem_Util is
          D := First_Elmt (Discriminant_Constraint (Desig_Typ));
          while Present (D) loop
             if Denotes_Discriminant (Node (D)) then
-               D_Val :=  Make_Selected_Component (Loc,
+               D_Val := Make_Selected_Component (Loc,
                  Prefix => New_Copy_Tree (P),
                 Selector_Name => New_Occurrence_Of (Entity (Node (D)), Loc));
 
@@ -7507,7 +7507,7 @@ package body Sem_Util is
                  ("Operation First for iterable type must be unique", Aspect);
                return Any_Type;
             else
-               Cursor :=  Etype (Func);
+               Cursor := Etype (Func);
             end if;
          end if;
 
diff --git a/gcc/ada/uintp.adb b/gcc/ada/uintp.adb
index 7a554392a79b..948c521b22e7 100644
--- a/gcc/ada/uintp.adb
+++ b/gcc/ada/uintp.adb
@@ -6,7 +6,7 @@
 --                                                                          --
 --                                 B o d y                                  --
 --                                                                          --
---          Copyright (C) 1992-2014, Free Software Foundation, Inc.         --
+--          Copyright (C) 1992-2015, 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- --
@@ -1586,7 +1586,7 @@ package body Uintp is
             --  Use prior single precision steps to compute this Euclid step
 
             --  For constructs such as:
-            --  sqrt_2: constant :=  1.41421_35623_73095_04880_16887_24209_698;
+            --  sqrt_2: constant := 1.41421_35623_73095_04880_16887_24209_698;
             --  sqrt_eps: constant long_float := long_float( 1.0 / sqrt_2)
             --    ** long_float'machine_mantissa;
             --
-- 
GitLab