diff --git a/gcc/ada/ChangeLog b/gcc/ada/ChangeLog
index 708e807d93ce794d138a6ae398f8b21ad1924b64..f8a0188dac2e9d7967ed6b7bea0b799170f02087 100644
--- a/gcc/ada/ChangeLog
+++ b/gcc/ada/ChangeLog
@@ -1,3 +1,8 @@
+2013-02-06  Robert Dewar  <dewar@adacore.com>
+
+	* sem_prag.adb, sem_ch6.adb, prj-conf.adb, erroutc.adb: Minor
+	reformatting.
+
 2013-02-06  Gary Dismukes  <dismukes@adacore.com>
 
 	* sem_ch6.adb (Check_For_Primitive_Subprogram): Test for
diff --git a/gcc/ada/erroutc.adb b/gcc/ada/erroutc.adb
index bb4995da9ee118b302be1f2bb4b5796e0ae39d60..8a1050fdd8a7417e083895d3906e6270c0a14d2f 100644
--- a/gcc/ada/erroutc.adb
+++ b/gcc/ada/erroutc.adb
@@ -1276,19 +1276,26 @@ package body Erroutc is
       for J in Specific_Warnings.First .. Specific_Warnings.Last loop
          declare
             SWE : Specific_Warning_Entry renames Specific_Warnings.Table (J);
+
          begin
             if not SWE.Config then
+
+               --  Warn for unmatched Warnings (Off, ...)
+
                if SWE.Open then
                   Eproc.all
                     ("?pragma Warnings Off with no matching Warnings On",
                      SWE.Start);
 
-               --  Do not issue this warning for -Wxxx messages since the
-               --  back-end doesn't report the information.
+               --  Warn for ineffective Warnings (Off, ..)
 
                elsif not SWE.Used
-                 and then not (SWE.Msg'Length > 2
-                                 and then SWE.Msg (1 .. 2) = "-W")
+
+                 --  Do not issue this warning for -Wxxx messages since the
+                 --  back-end doesn't report the information.
+
+                 and then not
+                   (SWE.Msg'Length > 2 and then SWE.Msg (1 .. 2) = "-W")
                then
                   Eproc.all
                     ("?no warning suppressed by this pragma", SWE.Start);
diff --git a/gcc/ada/prj-conf.adb b/gcc/ada/prj-conf.adb
index 89e1831959bd000104bb3d84eaf4a8e131676a62..42b91570b5e8a7a7b8913b89b661e50d41ae7d9c 100644
--- a/gcc/ada/prj-conf.adb
+++ b/gcc/ada/prj-conf.adb
@@ -2,7 +2,7 @@
 --                                                                          --
 --                         GNAT COMPILER COMPONENTS                         --
 --                                                                          --
---                             P R J . C O N F                             --
+--                             P R J . C O N F                              --
 --                                                                          --
 --                                 B o d y                                  --
 --                                                                          --
@@ -567,9 +567,8 @@ package body Prj.Conf is
 
       OK :=
         Target = ""
-        or else
-          (Tgt_Name /= No_Name
-           and then Target = Get_Name_String (Tgt_Name));
+          or else (Tgt_Name /= No_Name
+                    and then Target = Get_Name_String (Tgt_Name));
 
       if not OK then
          if Autoconf_Specified then
@@ -778,6 +777,7 @@ package body Prj.Conf is
       procedure Get_Project_Target is
       begin
          if Selected_Target'Length = 0 then
+
             --  Check if attribute Target is specified in the main
             --  project, or in a project it extends. If it is, use this
             --  target to invoke gprconfig.
@@ -1021,15 +1021,16 @@ package body Prj.Conf is
             else
                if Selected_Target'Length = 0 then
                   if At_Least_One_Compiler_Command then
-                     Args (4) := new String'("--target=all");
-
+                     Args (4) :=
+                       new String'("--target=all");
                   else
                      Args (4) :=
                        new String'("--target=" & Normalized_Hostname);
                   end if;
 
                else
-                  Args (4) := new String'("--target=" & Selected_Target.all);
+                  Args (4) :=
+                    new String'("--target=" & Selected_Target.all);
                end if;
 
                Arg_Last := 4;
diff --git a/gcc/ada/sem_ch6.adb b/gcc/ada/sem_ch6.adb
index e75b00da27958a3c8402f240816dae68c37313f3..4e63afea97e9ad80a63dab60e735d87762ff34ce 100644
--- a/gcc/ada/sem_ch6.adb
+++ b/gcc/ada/sem_ch6.adb
@@ -2909,6 +2909,9 @@ package body Sem_Ch6 is
         and then Serious_Errors_Detected = 0
         and then Present (Spec_Id)
         and then Has_Pragma_Inline (Spec_Id)
+
+        --  This test needs commenting ???
+
         and then In_Extended_Main_Code_Unit (N)
       then
          Check_And_Build_Body_To_Inline (N, Spec_Id, Body_Id);
diff --git a/gcc/ada/sem_prag.adb b/gcc/ada/sem_prag.adb
index 935a26d3bf9830bc6c986799e6842684ea4b5604..c7e340a3db0a4a4b9143c3016a979ab9704b41d4 100644
--- a/gcc/ada/sem_prag.adb
+++ b/gcc/ada/sem_prag.adb
@@ -16026,9 +16026,7 @@ package body Sem_Prag is
                                  J := J + 1;
                                  C := Get_String_Char (Str, J);
                                  Chr := Get_Character (C);
-                                 if Chr = 'W' then
-                                    exit;
-                                 end if;
+                                 exit when Chr = 'W';
                                  OK := False;
 
                               --  Dot case