diff --git a/gcc/ada/exp_ch4.adb b/gcc/ada/exp_ch4.adb
index cfdfefce5f3c06acf239e59ca365d37af650da91..ca23727399746dda459edcde3b95a3f722e04755 100644
--- a/gcc/ada/exp_ch4.adb
+++ b/gcc/ada/exp_ch4.adb
@@ -8170,26 +8170,18 @@ package body Exp_Ch4 is
            (Variant : Node_Id) return Boolean
          is
             Clist : constant Node_Id := Component_List (Variant);
+            Comp  : Node_Id := First (Component_Items (Clist));
 
          begin
-            if Is_Empty_List (Component_Items (Clist)) then
-               return False;
-            end if;
-
             --  We only need to test one component
 
-            declare
-               Comp : Node_Id := First (Component_Items (Clist));
-
-            begin
-               while Present (Comp) loop
-                  if Component_Is_Unconstrained_UU (Comp) then
-                     return True;
-                  end if;
+            while Present (Comp) loop
+               if Component_Is_Unconstrained_UU (Comp) then
+                  return True;
+               end if;
 
-                  Next (Comp);
-               end loop;
-            end;
+               Next (Comp);
+            end loop;
 
             --  None of the components withing the variant were of
             --  unconstrained Unchecked_Union type.
diff --git a/gcc/ada/exp_disp.adb b/gcc/ada/exp_disp.adb
index fcc719a220e39923dd9aca1b61058641f590581c..8bb72eb6d4a980421f52eafc0c8b5c60f6ba4af1 100644
--- a/gcc/ada/exp_disp.adb
+++ b/gcc/ada/exp_disp.adb
@@ -6640,28 +6640,25 @@ package body Exp_Disp is
       ----------------------
 
       function Find_Entry_Index (E : Entity_Id) return Uint is
-         Index     : Uint := Uint_1;
-         Subp_Decl : Entity_Id;
+         Index     : Uint := Uint_0;
+         Subp_Decl : Node_Id;
 
       begin
-         if Present (Decls)
-           and then not Is_Empty_List (Decls)
-         then
-            Subp_Decl := First (Decls);
-            while Present (Subp_Decl) loop
-               if Nkind (Subp_Decl) = N_Entry_Declaration then
-                  if Defining_Identifier (Subp_Decl) = E then
-                     return Index;
-                  end if;
+         Subp_Decl := First (Decls);
+         while Present (Subp_Decl) loop
+            if Nkind (Subp_Decl) = N_Entry_Declaration then
+               Index := Index + 1;
 
-                  Index := Index + 1;
+               if Defining_Identifier (Subp_Decl) = E then
+                  exit;
                end if;
 
-               Next (Subp_Decl);
-            end loop;
-         end if;
+            end if;
+
+            Next (Subp_Decl);
+         end loop;
 
-         return Uint_0;
+         return Index;
       end Find_Entry_Index;
 
       --  Local variables
diff --git a/gcc/ada/sem_ch12.adb b/gcc/ada/sem_ch12.adb
index f635f25647996bb7c0380db65bf57d69e85e887d..a0f1c11b26f7741d2935d312d87ceec9809c5475 100644
--- a/gcc/ada/sem_ch12.adb
+++ b/gcc/ada/sem_ch12.adb
@@ -16169,16 +16169,11 @@ package body Sem_Ch12 is
             pragma Assert (D /= Union_Id (No_List));
             --  Because No_List = Empty, which is in Node_Range above
 
-            if Is_Empty_List (List_Id (D)) then
-               null;
-
-            else
-               N1 := First (List_Id (D));
-               while Present (N1) loop
-                  Save_References (N1);
-                  Next (N1);
-               end loop;
-            end if;
+            N1 := First (List_Id (D));
+            while Present (N1) loop
+               Save_References (N1);
+               Next (N1);
+            end loop;
 
          --  Element list or other non-node field, nothing to do