diff --git a/gcc/ada/ChangeLog b/gcc/ada/ChangeLog
index 1d27923619d84c4476ffad53480274c270ec1407..ff25a9f6a7e3b983a562797d313d3a602d279bdf 100644
--- a/gcc/ada/ChangeLog
+++ b/gcc/ada/ChangeLog
@@ -1,3 +1,14 @@
+2010-11-02  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/gigi.h (add_stmt_force): Declare.
+	(add_stmt_with_node_force): Likewise.
+	* gcc-interface/trans.c (Attribute_to_gnu): Don't set TREE_SIDE_EFFECTS
+	on the SAVE_EXPR built for cached expressions of parameter attributes.
+	(Subprogram_Body_to_gnu): Force evaluation of the SAVE_EXPR built for
+	cached expressions of parameter attributes.
+	(add_stmt_force): New function.
+	(add_stmt_with_node_force): Likewise.
+
 2010-10-27  Eric Botcazou  <ebotcazou@adacore.com>
 
 	* gcc-interface/trans.c (gigi): Fix formatting issues.
diff --git a/gcc/ada/gcc-interface/gigi.h b/gcc/ada/gcc-interface/gigi.h
index 36966f96d5e39d62b9335e55d9d54386c46dc9a0..67a7a472abd251a11871c1e7d033fba5c47a17fc 100644
--- a/gcc/ada/gcc-interface/gigi.h
+++ b/gcc/ada/gcc-interface/gigi.h
@@ -57,12 +57,19 @@ extern void rest_of_type_decl_compilation (tree t);
 /* Start a new statement group chained to the previous group.  */
 extern void start_stmt_group (void);
 
-/* Add GNU_STMT to the current BLOCK_STMT node.  */
+/* Add GNU_STMT to the current statement group.  If it is an expression with
+   no effects, it is ignored.  */
 extern void add_stmt (tree gnu_stmt);
 
-/* Similar, but set the location of GNU_STMT to that of GNAT_NODE.  */
+/* Similar, but the statement is always added, regardless of side-effects.  */
+extern void add_stmt_force (tree gnu_stmt);
+
+/* Like add_stmt, but set the location of GNU_STMT to that of GNAT_NODE.  */
 extern void add_stmt_with_node (tree gnu_stmt, Node_Id gnat_node);
 
+/* Similar, but the statement is always added, regardless of side-effects.  */
+extern void add_stmt_with_node_force (tree gnu_stmt, Node_Id gnat_node);
+
 /* Return code corresponding to the current code group.  It is normally
    a STATEMENT_LIST, but may also be a BIND_EXPR or TRY_FINALLY_EXPR if
    BLOCK or cleanups were set.  */
diff --git a/gcc/ada/gcc-interface/trans.c b/gcc/ada/gcc-interface/trans.c
index 39dc0284d11b410874dcce98e471139a13aa708e..e0d17934d7bec3d553ac305c9f2a0cb7df29b9ef 100644
--- a/gcc/ada/gcc-interface/trans.c
+++ b/gcc/ada/gcc-interface/trans.c
@@ -1739,12 +1739,13 @@ Attribute_to_gnu (Node_Id gnat_node, tree *gnu_result_type_p, int attribute)
 
 	/* Cache the expression we have just computed.  Since we want to do it
 	   at run time, we force the use of a SAVE_EXPR and let the gimplifier
-	   create the temporary.  */
+	   create the temporary in the outermost binding level.  We will make
+	   sure in Subprogram_Body_to_gnu that it is evaluated on all possible
+	   paths by forcing its evaluation on entry of the function.  */
 	if (pa)
 	  {
 	    gnu_result
 	      = build1 (SAVE_EXPR, TREE_TYPE (gnu_result), gnu_result);
-	    TREE_SIDE_EFFECTS (gnu_result) = 1;
 	    if (attribute == Attr_First)
 	      pa->first = gnu_result;
 	    else if (attribute == Attr_Last)
@@ -2634,8 +2635,9 @@ Subprogram_Body_to_gnu (Node_Id gnat_node)
 
   VEC_pop (tree, gnu_return_label_stack);
 
-  /* If we populated the parameter attributes cache, we need to make sure
-     that the cached expressions are evaluated on all possible paths.  */
+  /* If we populated the parameter attributes cache, we need to make sure that
+     the cached expressions are evaluated on all the possible paths leading to
+     their uses.  So we force their evaluation on entry of the function.  */
   cache = DECL_STRUCT_FUNCTION (gnu_subprog_decl)->language->parm_attr_cache;
   if (cache)
     {
@@ -2647,11 +2649,11 @@ Subprogram_Body_to_gnu (Node_Id gnat_node)
       FOR_EACH_VEC_ELT (parm_attr, cache, i, pa)
 	{
 	  if (pa->first)
-	    add_stmt_with_node (pa->first, gnat_node);
+	    add_stmt_with_node_force (pa->first, gnat_node);
 	  if (pa->last)
-	    add_stmt_with_node (pa->last, gnat_node);
+	    add_stmt_with_node_force (pa->last, gnat_node);
 	  if (pa->length)
-	    add_stmt_with_node (pa->length, gnat_node);
+	    add_stmt_with_node_force (pa->length, gnat_node);
 	}
 
       add_stmt (gnu_result);
@@ -5969,7 +5971,8 @@ start_stmt_group (void)
   current_stmt_group = group;
 }
 
-/* Add GNU_STMT to the current statement group.  */
+/* Add GNU_STMT to the current statement group.  If it is an expression with
+   no effects, it is ignored.  */
 
 void
 add_stmt (tree gnu_stmt)
@@ -5977,7 +5980,15 @@ add_stmt (tree gnu_stmt)
   append_to_statement_list (gnu_stmt, &current_stmt_group->stmt_list);
 }
 
-/* Similar, but set the location of GNU_STMT to that of GNAT_NODE.  */
+/* Similar, but the statement is always added, regardless of side-effects.  */
+
+void
+add_stmt_force (tree gnu_stmt)
+{
+  append_to_statement_list_force (gnu_stmt, &current_stmt_group->stmt_list);
+}
+
+/* Like add_stmt, but set the location of GNU_STMT to that of GNAT_NODE.  */
 
 void
 add_stmt_with_node (tree gnu_stmt, Node_Id gnat_node)
@@ -5987,6 +5998,16 @@ add_stmt_with_node (tree gnu_stmt, Node_Id gnat_node)
   add_stmt (gnu_stmt);
 }
 
+/* Similar, but the statement is always added, regardless of side-effects.  */
+
+void
+add_stmt_with_node_force (tree gnu_stmt, Node_Id gnat_node)
+{
+  if (Present (gnat_node))
+    set_expr_location_from_node (gnu_stmt, gnat_node);
+  add_stmt_force (gnu_stmt);
+}
+
 /* Add a declaration statement for GNU_DECL to the current statement group.
    Get SLOC from Entity_Id.  */
 
diff --git a/gcc/testsuite/ChangeLog b/gcc/testsuite/ChangeLog
index c4841177d2b359cff0830944d47c4f1a40214ecd..87da982a36d81304d32329f8cc22e1966e3e96ff 100644
--- a/gcc/testsuite/ChangeLog
+++ b/gcc/testsuite/ChangeLog
@@ -1,3 +1,7 @@
+2010-11-02  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gnat.dg/sizetype4.adb: New test.
+
 2010-11-02  H.J. Lu  <hongjiu.lu@intel.com>
 
 	* gcc.target/i386/avx-vzeroupper-15.c: New.
diff --git a/gcc/testsuite/gnat.dg/sizetype4.adb b/gcc/testsuite/gnat.dg/sizetype4.adb
new file mode 100644
index 0000000000000000000000000000000000000000..b3ff6431961f9194243780b4a916254414e6acb3
--- /dev/null
+++ b/gcc/testsuite/gnat.dg/sizetype4.adb
@@ -0,0 +1,25 @@
+-- { dg-do run }
+
+procedure Sizetype4 is
+
+   type Float_Array is array (Integer range <>) of Float;
+   NoFloats : Float_Array (1 .. 0);
+
+   procedure Q (Results : Float_Array := NoFloats) is
+
+      type Reply_Msg is
+         record
+            Request_Id : Integer;
+            Status     : Integer;
+            Data       : Float_Array (Results'Range);
+         end record;
+
+   begin
+      if Reply_Msg'Size /= 64 then
+        raise Program_Error;
+      end if;
+   end;
+
+begin
+   Q;
+end;