diff --git a/gcc/testsuite/ChangeLog b/gcc/testsuite/ChangeLog
index 7aacd2f3668654f90c89e86da492d8b5fe9ed11f..ef8a58fcd571eb90c1487329a2a17c6c621d5de9 100644
--- a/gcc/testsuite/ChangeLog
+++ b/gcc/testsuite/ChangeLog
@@ -1,3 +1,10 @@
+2005-06-07  Thomas Koenig  <Thomas.Koenig@online.de>
+
+	PR libfortran/21926
+	* gfortran.fortran-torture/execute/intrinsic_matmul.f90:
+	Test case where the return array has lowest stride one,
+	but isn't packed.
+
 2005-06-07  Adrian Straetling  <straetling@de.ibm.com>
 
 	* lib/target-supports.exp (check_effective_target_sync_int_long):
diff --git a/gcc/testsuite/gfortran.fortran-torture/execute/intrinsic_matmul.f90 b/gcc/testsuite/gfortran.fortran-torture/execute/intrinsic_matmul.f90
index 4b195d267bd182fb5653bc36597c6010fefef3e6..9364f1e1d8b0c620114cb08e6735dc342aaa2db2 100644
--- a/gcc/testsuite/gfortran.fortran-torture/execute/intrinsic_matmul.f90
+++ b/gcc/testsuite/gfortran.fortran-torture/execute/intrinsic_matmul.f90
@@ -7,6 +7,8 @@ program intrinsic_matmul
    integer, dimension(3) :: y
    integer, dimension(2, 2) :: r
    integer, dimension(3) :: v
+   real, dimension (2,2) :: aa
+   real, dimension (4,2) :: cc
 
    a = reshape((/1, 2, 2, 3, 3, 4/), (/2, 3/))
    b = reshape((/1, 2, 3, 3, 4, 5/), (/3, 2/))
@@ -21,4 +23,10 @@ program intrinsic_matmul
 
    v(1:2) = matmul(a, y)
    if (any(v(1:2) .ne. (/14, 20/))) call abort
+
+  aa = reshape((/ 1.0, 1.0, 0.0, 1.0/), shape(aa))
+  cc = 42.
+  cc(1:2,1:2) = matmul(aa, transpose(aa))
+  if (any(cc(1:2,1:2) .ne. reshape((/ 1.0, 1.0, 1.0, 2.0 /), (/2,2/)))) call abort
+  if (any(cc(3:4,1:2) .ne. 42.)) call abort
 end program
diff --git a/libgfortran/ChangeLog b/libgfortran/ChangeLog
index b912b31adcf592132b78c0b58487db12b43d442c..ac9fce5281b7ccc7656a1f09be2b8737b64ca634 100644
--- a/libgfortran/ChangeLog
+++ b/libgfortran/ChangeLog
@@ -1,3 +1,15 @@
+2005-06-07  Thomas Koenig  <Thomas.Koenig@online.de>
+
+	PR libfortran/21926
+	* m4/matmul.m4:  Correct zeroing of result for non-packed
+	arrays with lowest stride is one.
+	* generated/matmul_c4.c:  Regenerated.
+	* generated/matmul_c8.c:  Regenerated.
+	* generated/matmul_i4.c:  Regenerated.
+	* generated/matmul_i8.c:  Regenerated.
+	* generated/matmul_r4.c:  Regenerated.
+	* generated/matmul_r8.c:  Regenerated.
+
 2005-05-30  Francois-Xavier Coudert  <coudert@clipper.ens.fr>
 
 	PR libfortran/20179
diff --git a/libgfortran/generated/matmul_c4.c b/libgfortran/generated/matmul_c4.c
index 5eb8b44631ba9ea5b2e732d8d570743807206016..c63d343ea82e92ff5459fff0ff57216b07708ad6 100644
--- a/libgfortran/generated/matmul_c4.c
+++ b/libgfortran/generated/matmul_c4.c
@@ -178,7 +178,14 @@ matmul_c4 (gfc_array_c4 * retarray, gfc_array_c4 * a, gfc_array_c4 * b)
       GFC_COMPLEX_4 *abase_n;
       GFC_COMPLEX_4 bbase_yn;
 
-      memset (dest, 0, (sizeof (GFC_COMPLEX_4) * size0((array_t *) retarray)));
+      if (rystride == ycount)
+	memset (dest, 0, (sizeof (GFC_COMPLEX_4) * size0((array_t *) retarray)));
+      else
+	{
+	  for (y = 0; y < ycount; y++)
+	    for (x = 0; x < xcount; x++)
+	      dest[x + y*rystride] = (GFC_COMPLEX_4)0;
+	}
 
       for (y = 0; y < ycount; y++)
 	{
diff --git a/libgfortran/generated/matmul_c8.c b/libgfortran/generated/matmul_c8.c
index 181f4c9cc4d14e08058e91902f56810729720689..98326d135d89283f38540d0c34820b2eb13622b8 100644
--- a/libgfortran/generated/matmul_c8.c
+++ b/libgfortran/generated/matmul_c8.c
@@ -178,7 +178,14 @@ matmul_c8 (gfc_array_c8 * retarray, gfc_array_c8 * a, gfc_array_c8 * b)
       GFC_COMPLEX_8 *abase_n;
       GFC_COMPLEX_8 bbase_yn;
 
-      memset (dest, 0, (sizeof (GFC_COMPLEX_8) * size0((array_t *) retarray)));
+      if (rystride == ycount)
+	memset (dest, 0, (sizeof (GFC_COMPLEX_8) * size0((array_t *) retarray)));
+      else
+	{
+	  for (y = 0; y < ycount; y++)
+	    for (x = 0; x < xcount; x++)
+	      dest[x + y*rystride] = (GFC_COMPLEX_8)0;
+	}
 
       for (y = 0; y < ycount; y++)
 	{
diff --git a/libgfortran/generated/matmul_i4.c b/libgfortran/generated/matmul_i4.c
index f214ba5ec0c8108a1e0aa600adbd8a895a84ab9f..9dde570b73a49ac6ff106efcfba2b820771112e2 100644
--- a/libgfortran/generated/matmul_i4.c
+++ b/libgfortran/generated/matmul_i4.c
@@ -178,7 +178,14 @@ matmul_i4 (gfc_array_i4 * retarray, gfc_array_i4 * a, gfc_array_i4 * b)
       GFC_INTEGER_4 *abase_n;
       GFC_INTEGER_4 bbase_yn;
 
-      memset (dest, 0, (sizeof (GFC_INTEGER_4) * size0((array_t *) retarray)));
+      if (rystride == ycount)
+	memset (dest, 0, (sizeof (GFC_INTEGER_4) * size0((array_t *) retarray)));
+      else
+	{
+	  for (y = 0; y < ycount; y++)
+	    for (x = 0; x < xcount; x++)
+	      dest[x + y*rystride] = (GFC_INTEGER_4)0;
+	}
 
       for (y = 0; y < ycount; y++)
 	{
diff --git a/libgfortran/generated/matmul_i8.c b/libgfortran/generated/matmul_i8.c
index 5e0e6a792f969e254bd96f95d97b92502005121e..18d877e20f99baf7084e37b61fe949dbd3dbf252 100644
--- a/libgfortran/generated/matmul_i8.c
+++ b/libgfortran/generated/matmul_i8.c
@@ -178,7 +178,14 @@ matmul_i8 (gfc_array_i8 * retarray, gfc_array_i8 * a, gfc_array_i8 * b)
       GFC_INTEGER_8 *abase_n;
       GFC_INTEGER_8 bbase_yn;
 
-      memset (dest, 0, (sizeof (GFC_INTEGER_8) * size0((array_t *) retarray)));
+      if (rystride == ycount)
+	memset (dest, 0, (sizeof (GFC_INTEGER_8) * size0((array_t *) retarray)));
+      else
+	{
+	  for (y = 0; y < ycount; y++)
+	    for (x = 0; x < xcount; x++)
+	      dest[x + y*rystride] = (GFC_INTEGER_8)0;
+	}
 
       for (y = 0; y < ycount; y++)
 	{
diff --git a/libgfortran/generated/matmul_r4.c b/libgfortran/generated/matmul_r4.c
index b6014d0dbce52c2913ca709083d1088ac5211471..642dc9438377e0c5bf302f02e843869f4bed4ef5 100644
--- a/libgfortran/generated/matmul_r4.c
+++ b/libgfortran/generated/matmul_r4.c
@@ -178,7 +178,14 @@ matmul_r4 (gfc_array_r4 * retarray, gfc_array_r4 * a, gfc_array_r4 * b)
       GFC_REAL_4 *abase_n;
       GFC_REAL_4 bbase_yn;
 
-      memset (dest, 0, (sizeof (GFC_REAL_4) * size0((array_t *) retarray)));
+      if (rystride == ycount)
+	memset (dest, 0, (sizeof (GFC_REAL_4) * size0((array_t *) retarray)));
+      else
+	{
+	  for (y = 0; y < ycount; y++)
+	    for (x = 0; x < xcount; x++)
+	      dest[x + y*rystride] = (GFC_REAL_4)0;
+	}
 
       for (y = 0; y < ycount; y++)
 	{
diff --git a/libgfortran/generated/matmul_r8.c b/libgfortran/generated/matmul_r8.c
index 5bf21f60404cedbb0b969308dece60f2156f2164..1eb53cd6c673a6abac63419ffb9cc02d1ab24eae 100644
--- a/libgfortran/generated/matmul_r8.c
+++ b/libgfortran/generated/matmul_r8.c
@@ -178,7 +178,14 @@ matmul_r8 (gfc_array_r8 * retarray, gfc_array_r8 * a, gfc_array_r8 * b)
       GFC_REAL_8 *abase_n;
       GFC_REAL_8 bbase_yn;
 
-      memset (dest, 0, (sizeof (GFC_REAL_8) * size0((array_t *) retarray)));
+      if (rystride == ycount)
+	memset (dest, 0, (sizeof (GFC_REAL_8) * size0((array_t *) retarray)));
+      else
+	{
+	  for (y = 0; y < ycount; y++)
+	    for (x = 0; x < xcount; x++)
+	      dest[x + y*rystride] = (GFC_REAL_8)0;
+	}
 
       for (y = 0; y < ycount; y++)
 	{
diff --git a/libgfortran/m4/matmul.m4 b/libgfortran/m4/matmul.m4
index dd75cf7b0738de495eb2b371d7655ba1f291b9a6..1801583f02621a97ab0bc11a9d470bdb5590224b 100644
--- a/libgfortran/m4/matmul.m4
+++ b/libgfortran/m4/matmul.m4
@@ -180,7 +180,14 @@ sinclude(`matmul_asm_'rtype_code`.m4')dnl
       rtype_name *abase_n;
       rtype_name bbase_yn;
 
-      memset (dest, 0, (sizeof (rtype_name) * size0((array_t *) retarray)));
+      if (rystride == ycount)
+	memset (dest, 0, (sizeof (rtype_name) * size0((array_t *) retarray)));
+      else
+	{
+	  for (y = 0; y < ycount; y++)
+	    for (x = 0; x < xcount; x++)
+	      dest[x + y*rystride] = (rtype_name)0;
+	}
 
       for (y = 0; y < ycount; y++)
 	{