diff --git a/gcc/fortran/ChangeLog b/gcc/fortran/ChangeLog
index 1b62f79d09c6c48c1ed04230bec4828f914fee8b..94db2b47d246ecd0c0b438d45de60baee9971bb3 100644
--- a/gcc/fortran/ChangeLog
+++ b/gcc/fortran/ChangeLog
@@ -1,3 +1,10 @@
+2006-05-19  H.J. Lu  <hongjiu.lu@intel.com>
+
+	PR fortran/27662
+	* trans-array.c (gfc_conv_expr_descriptor): Don't zere the
+	first stride to indicate a temporary.
+	* trans-expr.c (gfc_conv_function_call): Likewise.
+
 2006-05-18  Francois-Xavier Coudert  <coudert@clipper.ens.fr>
 	    Feng Wang  <fengwang@nudt.edu.cn>
 
diff --git a/gcc/fortran/trans-array.c b/gcc/fortran/trans-array.c
index 7e9d5a65ef0503f80e30c13d1f2f2b311c5728ee..32283a3df06d074b5de9be680ea66f13dc6dae19 100644
--- a/gcc/fortran/trans-array.c
+++ b/gcc/fortran/trans-array.c
@@ -4108,10 +4108,7 @@ gfc_conv_expr_descriptor (gfc_se * se, gfc_expr * expr, gfc_ss * ss)
       /* Finish the copying loops.  */
       gfc_trans_scalarizing_loops (&loop, &block);
 
-      /* Set the first stride component to zero to indicate a temporary.  */
       desc = loop.temp_ss->data.info.descriptor;
-      tmp = gfc_conv_descriptor_stride (desc, gfc_rank_cst[0]);
-      gfc_add_modify_expr (&loop.pre, tmp, gfc_index_zero_node);
 
       gcc_assert (is_gimple_lvalue (desc));
     }
diff --git a/gcc/fortran/trans-expr.c b/gcc/fortran/trans-expr.c
index 4eceab6876ec64bd39d6c303d13a9c2b15436417..b91ebf6a663baab70f4bedf6a98d522b42c83c6f 100644
--- a/gcc/fortran/trans-expr.c
+++ b/gcc/fortran/trans-expr.c
@@ -2038,11 +2038,6 @@ gfc_conv_function_call (gfc_se * se, gfc_symbol * sym,
 	  gfc_trans_create_temp_array (&se->pre, &se->post, se->loop, info, tmp,
 				       false, !sym->attr.pointer, callee_alloc);
 
-	  /* Zero the first stride to indicate a temporary.  */
-	  tmp = gfc_conv_descriptor_stride (info->descriptor, gfc_rank_cst[0]);
-	  gfc_add_modify_expr (&se->pre, tmp,
-			       convert (TREE_TYPE (tmp), integer_zero_node));
-
 	  /* Pass the temporary as the first argument.  */
 	  tmp = info->descriptor;
 	  tmp = build_fold_addr_expr (tmp);
diff --git a/gcc/testsuite/ChangeLog b/gcc/testsuite/ChangeLog
index 50bbc7c132e819a80b679a3cedb9d343b3c6cb43..c5b0bffc9fc1c24789a65d4721faa8e50b612c83 100644
--- a/gcc/testsuite/ChangeLog
+++ b/gcc/testsuite/ChangeLog
@@ -1,3 +1,8 @@
+2006-05-19  H.J. Lu  <hongjiu.lu@intel.com>
+
+	PR fortran/27662
+	* gfortran.dg/temporary_1.f90: New file.
+
 2006-05-19  Andreas Schwab  <schwab@suse.de>
 
 	* g++.dg/other/unused1.C: Also match "stringz".
diff --git a/gcc/testsuite/gfortran.dg/temporary_1.f90 b/gcc/testsuite/gfortran.dg/temporary_1.f90
new file mode 100644
index 0000000000000000000000000000000000000000..e255efdb7a88bf90d754804d534054f16c20cfa8
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/temporary_1.f90
@@ -0,0 +1,28 @@
+! { dg-do run }
+! PR 27662. Don't zero the first stride to indicate a temporary. It
+! may be used later.
+program pr27662
+ implicit none
+ real(kind=kind(1.0d0)), dimension (2, 2):: x, y, z;
+ integer i, j
+ x(1,1) = 1.d0 
+ x(2,1) = 0.d0
+ x(1,2) = 0.d0
+ x(2,2) = 1.d0 
+ z = matmul (x, transpose (test ()))
+ do i = 1, size (x, 1)
+   do j = 1, size (x, 2)
+     if (x (i, j) .ne. z (i, j)) call abort ()
+   end do
+ end do
+ close (10)
+
+contains
+ function test () result (res)
+   real(kind=kind(1.0d0)), dimension(2,2) :: res
+   res(1,1) = 1.d0 
+   res(2,1) = 0.d0
+   res(1,2) = 0.d0
+   res(2,2) = 1.d0 
+ end function
+end