diff --git a/gcc/ada/ChangeLog b/gcc/ada/ChangeLog
index 80103fb053a0757cf09cf31539fc902c0b0a8bdf..c5388ac456e9dcc13725c1a394a059520c33a348 100644
--- a/gcc/ada/ChangeLog
+++ b/gcc/ada/ChangeLog
@@ -1,3 +1,9 @@
+2009-10-17  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/utils.c (convert): When converting to a padded type
+	with an inner type of self-referential size, pad the expression before
+	doing the unchecked conversion.
+
 2009-10-17  Eric Botcazou  <ebotcazou@adacore.com>
 
 	* gcc-interface/utils2.c (build_binary_op) <ARRAY_RANGE_REF>: Mak
diff --git a/gcc/ada/gcc-interface/utils.c b/gcc/ada/gcc-interface/utils.c
index 86575b529d953115250978382e1e7b636f8fdf6c..a8225b0b30a9d5633a3f29f0e2847da85d4a10f1 100644
--- a/gcc/ada/gcc-interface/utils.c
+++ b/gcc/ada/gcc-interface/utils.c
@@ -3856,12 +3856,17 @@ convert (tree type, tree expr)
 		     == TYPE_NAME (TREE_TYPE (TYPE_FIELDS (type))))))
 	return convert (type, TREE_OPERAND (expr, 0));
 
-      /* If the result type is a padded type with a self-referentially-sized
-	 field and the expression type is a record, do this as an unchecked
-	 conversion.  */
+      /* If the inner type is of self-referential size and the expression type
+	 is a record, do this as an unchecked conversion.  But first pad the
+	 expression if possible to have the same size on both sides.  */
       if (TREE_CODE (etype) == RECORD_TYPE
 	  && CONTAINS_PLACEHOLDER_P (DECL_SIZE (TYPE_FIELDS (type))))
-	return unchecked_convert (type, expr, false);
+	{
+	  if (TREE_CONSTANT (TYPE_SIZE (etype)))
+	    expr = convert (maybe_pad_type (etype, TYPE_SIZE (type), 0, Empty,
+			    false, false, false, true), expr);
+	  return unchecked_convert (type, expr, false);
+	}
 
       /* If we are converting between array types with variable size, do the
 	 final conversion as an unchecked conversion, again to avoid the need
diff --git a/gcc/testsuite/ChangeLog b/gcc/testsuite/ChangeLog
index acbbe3619151ddd208cdc2f81befc37545d9f230..2e9f67d46baf6f6439e688cc367fac657fc11212 100644
--- a/gcc/testsuite/ChangeLog
+++ b/gcc/testsuite/ChangeLog
@@ -1,3 +1,8 @@
+2009-10-17  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gnat.dg/aggr11.adb: New test.
+	* gnat.dg/aggr11_pkg.ads: New helper.
+
 2009-10-17  Eric Botcazou  <ebotcazou@adacore.com>
 
 	* gnat.dg/slice8.adb: New test.
diff --git a/gcc/testsuite/gnat.dg/aggr11.adb b/gcc/testsuite/gnat.dg/aggr11.adb
new file mode 100644
index 0000000000000000000000000000000000000000..1771d62cacb54557d4e0852779229e54ab3e7bff
--- /dev/null
+++ b/gcc/testsuite/gnat.dg/aggr11.adb
@@ -0,0 +1,17 @@
+-- { dg-do compile }
+-- { dg-options "-O" }
+
+with Aggr11_Pkg; use Aggr11_Pkg;
+
+procedure Aggr11 is
+
+  A : Arr := ((1 => (Kind  => No_Error, B => True),
+               2 => (Kind => Error),
+               3 => (Kind => Error),
+               4 => (Kind  => No_Error, B => True),
+               5 => (Kind  => No_Error, B => True),
+               6 => (Kind  => No_Error, B => True)));
+
+begin
+   null;
+end;
diff --git a/gcc/testsuite/gnat.dg/aggr11_pkg.ads b/gcc/testsuite/gnat.dg/aggr11_pkg.ads
new file mode 100644
index 0000000000000000000000000000000000000000..37008605a30e0a2185a65690c740e22886ba91b2
--- /dev/null
+++ b/gcc/testsuite/gnat.dg/aggr11_pkg.ads
@@ -0,0 +1,14 @@
+package Aggr11_Pkg is
+
+   type Error_Type is (No_Error, Error);
+
+   type Rec (Kind : Error_Type := No_Error) is record
+     case Kind is
+       when Error => null;
+       when others => B : Boolean;
+     end case;
+   end record;
+
+   type Arr is array (1..6) of Rec;
+
+end Aggr11_Pkg;