diff --git a/gcc/testsuite/ChangeLog b/gcc/testsuite/ChangeLog
index c3cccc5e596fcdf6143d6a712d3e9481a6cb5765..277f767a38a64102989e0e4a84be824fd2c70f3e 100644
--- a/gcc/testsuite/ChangeLog
+++ b/gcc/testsuite/ChangeLog
@@ -1,3 +1,8 @@
+2006-05-05  Francois-Xavier Coudert  <coudert@clipper.ens.fr>
+
+	PR libfortran/26985
+	* gfortran.dg/matmul_2.f90: New test.
+	
 2005-05-05  Laurent GUERBY  <laurent@guerby.net>
 
 	* ada/acats/run_all.sh: Use sync when main not found.
diff --git a/gcc/testsuite/gfortran.dg/matmul_2.f90 b/gcc/testsuite/gfortran.dg/matmul_2.f90
new file mode 100644
index 0000000000000000000000000000000000000000..fb678afb896f5884837267948058be9f4c3147ea
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/matmul_2.f90
@@ -0,0 +1,21 @@
+!{ dg-do run }
+! PR libfortran/26985
+program matmul_2
+  implicit none
+  integer :: a(2,9), b(9,7), c(2,7)
+  integer :: i, j
+
+  a = 1
+  b = 2
+  c = 1789789
+  c(:,1:7:2) = matmul(a,b(:,1:7:2))
+
+  if (c(1,1) /= 18 .or. c(2,1) /= 18 .or. &
+      c(1,2) /= 1789789 .or. c(2,2) /= 1789789 .or. &
+      c(1,3) /= 18 .or. c(2,3) /= 18 .or. &
+      c(1,4) /= 1789789 .or. c(2,4) /= 1789789 .or. &
+      c(1,5) /= 18 .or. c(2,5) /= 18 .or. &
+      c(1,6) /= 1789789 .or. c(2,6) /= 1789789 .or. &
+      c(1,7) /= 18 .or. c(2,7) /= 18) call abort
+      
+end program matmul_2
diff --git a/libgfortran/ChangeLog b/libgfortran/ChangeLog
index 90537156703670bdc29af997ad79934113c3b733..cb8c0fd1c282af48fd32bc8e9dc905dd6b1e6ba1 100644
--- a/libgfortran/ChangeLog
+++ b/libgfortran/ChangeLog
@@ -1,7 +1,23 @@
+2006-05-05  Francois-Xavier Coudert  <coudert@clipper.ens.fr>
+
+	PR libfortran/26985
+	* m4/matmul.m4: Correct the condition for the memset call,
+	and remove the unneeded call to size0.
+	* generated/matmul_r4.c: Regenerate.
+	* generated/matmul_r8.c: Regenerate.
+	* generated/matmul_r10.c: Regenerate.
+	* generated/matmul_r16.c: Regenerate.
+	* generated/matmul_c4.c: Regenerate.
+	* generated/matmul_c8.c: Regenerate.
+	* generated/matmul_c10.c: Regenerate.
+	* generated/matmul_c16.c: Regenerate.
+	* generated/matmul_i4.c: Regenerate.
+	* generated/matmul_i8.c: Regenerate.
+	* generated/matmul_i16.c: Regenerate.
+
 2006-04-29  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
 
 	PR libgfortran/27360
-	
 	* io/list_read.c (read_logical):  Free line_buffer and free saved.
 
 2006-04-28  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
diff --git a/libgfortran/generated/matmul_c10.c b/libgfortran/generated/matmul_c10.c
index edbd1e6becceb08a9cffaa3d105ed7c0c829f4ae..93032f81404727bc0309c00e3a6b3701c810b1b6 100644
--- a/libgfortran/generated/matmul_c10.c
+++ b/libgfortran/generated/matmul_c10.c
@@ -193,8 +193,8 @@ matmul_c10 (gfc_array_c10 * const restrict retarray,
       const GFC_COMPLEX_10 * restrict abase_n;
       GFC_COMPLEX_10 bbase_yn;
 
-      if (rystride == ycount)
-	memset (dest, 0, (sizeof (GFC_COMPLEX_10) * size0((array_t *) retarray)));
+      if (rystride == xcount)
+	memset (dest, 0, (sizeof (GFC_COMPLEX_10) * xcount * ycount));
       else
 	{
 	  for (y = 0; y < ycount; y++)
diff --git a/libgfortran/generated/matmul_c16.c b/libgfortran/generated/matmul_c16.c
index c04146be821990b1365662c5a60f9122e6402b4d..03ad0f7df27d35633122f4d065844a0437b55447 100644
--- a/libgfortran/generated/matmul_c16.c
+++ b/libgfortran/generated/matmul_c16.c
@@ -193,8 +193,8 @@ matmul_c16 (gfc_array_c16 * const restrict retarray,
       const GFC_COMPLEX_16 * restrict abase_n;
       GFC_COMPLEX_16 bbase_yn;
 
-      if (rystride == ycount)
-	memset (dest, 0, (sizeof (GFC_COMPLEX_16) * size0((array_t *) retarray)));
+      if (rystride == xcount)
+	memset (dest, 0, (sizeof (GFC_COMPLEX_16) * xcount * ycount));
       else
 	{
 	  for (y = 0; y < ycount; y++)
diff --git a/libgfortran/generated/matmul_c4.c b/libgfortran/generated/matmul_c4.c
index a01de37bc74a593829073b48570266518c0451b3..84c94cd586fda0c2085cc988163c898941d41c02 100644
--- a/libgfortran/generated/matmul_c4.c
+++ b/libgfortran/generated/matmul_c4.c
@@ -193,8 +193,8 @@ matmul_c4 (gfc_array_c4 * const restrict retarray,
       const GFC_COMPLEX_4 * restrict abase_n;
       GFC_COMPLEX_4 bbase_yn;
 
-      if (rystride == ycount)
-	memset (dest, 0, (sizeof (GFC_COMPLEX_4) * size0((array_t *) retarray)));
+      if (rystride == xcount)
+	memset (dest, 0, (sizeof (GFC_COMPLEX_4) * xcount * ycount));
       else
 	{
 	  for (y = 0; y < ycount; y++)
diff --git a/libgfortran/generated/matmul_c8.c b/libgfortran/generated/matmul_c8.c
index 75ec4fc101c1a32ee73b6a84d796ec271b46f688..f491ea058d7df6a93732a4a99ba61282ebca1237 100644
--- a/libgfortran/generated/matmul_c8.c
+++ b/libgfortran/generated/matmul_c8.c
@@ -193,8 +193,8 @@ matmul_c8 (gfc_array_c8 * const restrict retarray,
       const GFC_COMPLEX_8 * restrict abase_n;
       GFC_COMPLEX_8 bbase_yn;
 
-      if (rystride == ycount)
-	memset (dest, 0, (sizeof (GFC_COMPLEX_8) * size0((array_t *) retarray)));
+      if (rystride == xcount)
+	memset (dest, 0, (sizeof (GFC_COMPLEX_8) * xcount * ycount));
       else
 	{
 	  for (y = 0; y < ycount; y++)
diff --git a/libgfortran/generated/matmul_i16.c b/libgfortran/generated/matmul_i16.c
index eacc47ff8cd1d8e88f4eb42ddd847b3efb9f9a72..50d87bb8b0fcc2e2dbfa03045eb977006198edc1 100644
--- a/libgfortran/generated/matmul_i16.c
+++ b/libgfortran/generated/matmul_i16.c
@@ -193,8 +193,8 @@ matmul_i16 (gfc_array_i16 * const restrict retarray,
       const GFC_INTEGER_16 * restrict abase_n;
       GFC_INTEGER_16 bbase_yn;
 
-      if (rystride == ycount)
-	memset (dest, 0, (sizeof (GFC_INTEGER_16) * size0((array_t *) retarray)));
+      if (rystride == xcount)
+	memset (dest, 0, (sizeof (GFC_INTEGER_16) * xcount * ycount));
       else
 	{
 	  for (y = 0; y < ycount; y++)
diff --git a/libgfortran/generated/matmul_i4.c b/libgfortran/generated/matmul_i4.c
index 6166bf18c29115a95f68b034c2954328df19a322..12ac630a549190e0a5197ee4483b480ee9cf37a1 100644
--- a/libgfortran/generated/matmul_i4.c
+++ b/libgfortran/generated/matmul_i4.c
@@ -193,8 +193,8 @@ matmul_i4 (gfc_array_i4 * const restrict retarray,
       const GFC_INTEGER_4 * restrict abase_n;
       GFC_INTEGER_4 bbase_yn;
 
-      if (rystride == ycount)
-	memset (dest, 0, (sizeof (GFC_INTEGER_4) * size0((array_t *) retarray)));
+      if (rystride == xcount)
+	memset (dest, 0, (sizeof (GFC_INTEGER_4) * xcount * ycount));
       else
 	{
 	  for (y = 0; y < ycount; y++)
diff --git a/libgfortran/generated/matmul_i8.c b/libgfortran/generated/matmul_i8.c
index b83ded04ebf02698974720302237075be5b62be8..82b22292632ed7667c87aea688027420e3ca632f 100644
--- a/libgfortran/generated/matmul_i8.c
+++ b/libgfortran/generated/matmul_i8.c
@@ -193,8 +193,8 @@ matmul_i8 (gfc_array_i8 * const restrict retarray,
       const GFC_INTEGER_8 * restrict abase_n;
       GFC_INTEGER_8 bbase_yn;
 
-      if (rystride == ycount)
-	memset (dest, 0, (sizeof (GFC_INTEGER_8) * size0((array_t *) retarray)));
+      if (rystride == xcount)
+	memset (dest, 0, (sizeof (GFC_INTEGER_8) * xcount * ycount));
       else
 	{
 	  for (y = 0; y < ycount; y++)
diff --git a/libgfortran/generated/matmul_r10.c b/libgfortran/generated/matmul_r10.c
index 6702209bd228789f71f799b6def56e0b94b85fd3..73e1e32763085660cacf2be28a08f439919b540b 100644
--- a/libgfortran/generated/matmul_r10.c
+++ b/libgfortran/generated/matmul_r10.c
@@ -193,8 +193,8 @@ matmul_r10 (gfc_array_r10 * const restrict retarray,
       const GFC_REAL_10 * restrict abase_n;
       GFC_REAL_10 bbase_yn;
 
-      if (rystride == ycount)
-	memset (dest, 0, (sizeof (GFC_REAL_10) * size0((array_t *) retarray)));
+      if (rystride == xcount)
+	memset (dest, 0, (sizeof (GFC_REAL_10) * xcount * ycount));
       else
 	{
 	  for (y = 0; y < ycount; y++)
diff --git a/libgfortran/generated/matmul_r16.c b/libgfortran/generated/matmul_r16.c
index c095cbdb747a4ef8dd30dc9ef1c985a3c7a4df83..099c6bf855ed39bf3321917a89d13a1244a7dd70 100644
--- a/libgfortran/generated/matmul_r16.c
+++ b/libgfortran/generated/matmul_r16.c
@@ -193,8 +193,8 @@ matmul_r16 (gfc_array_r16 * const restrict retarray,
       const GFC_REAL_16 * restrict abase_n;
       GFC_REAL_16 bbase_yn;
 
-      if (rystride == ycount)
-	memset (dest, 0, (sizeof (GFC_REAL_16) * size0((array_t *) retarray)));
+      if (rystride == xcount)
+	memset (dest, 0, (sizeof (GFC_REAL_16) * xcount * ycount));
       else
 	{
 	  for (y = 0; y < ycount; y++)
diff --git a/libgfortran/generated/matmul_r4.c b/libgfortran/generated/matmul_r4.c
index dedc5a3496162d51a35da08700156aa559028b36..ca6a4a4360cab9f98b177c9f6e624c3cd4a401ae 100644
--- a/libgfortran/generated/matmul_r4.c
+++ b/libgfortran/generated/matmul_r4.c
@@ -193,8 +193,8 @@ matmul_r4 (gfc_array_r4 * const restrict retarray,
       const GFC_REAL_4 * restrict abase_n;
       GFC_REAL_4 bbase_yn;
 
-      if (rystride == ycount)
-	memset (dest, 0, (sizeof (GFC_REAL_4) * size0((array_t *) retarray)));
+      if (rystride == xcount)
+	memset (dest, 0, (sizeof (GFC_REAL_4) * xcount * ycount));
       else
 	{
 	  for (y = 0; y < ycount; y++)
diff --git a/libgfortran/generated/matmul_r8.c b/libgfortran/generated/matmul_r8.c
index 926a860e386e5677dd7acd004392555d368895e2..1844cdc3da8a0a4163c21efc725fbb1033e5b608 100644
--- a/libgfortran/generated/matmul_r8.c
+++ b/libgfortran/generated/matmul_r8.c
@@ -193,8 +193,8 @@ matmul_r8 (gfc_array_r8 * const restrict retarray,
       const GFC_REAL_8 * restrict abase_n;
       GFC_REAL_8 bbase_yn;
 
-      if (rystride == ycount)
-	memset (dest, 0, (sizeof (GFC_REAL_8) * size0((array_t *) retarray)));
+      if (rystride == xcount)
+	memset (dest, 0, (sizeof (GFC_REAL_8) * xcount * ycount));
       else
 	{
 	  for (y = 0; y < ycount; y++)
diff --git a/libgfortran/m4/matmul.m4 b/libgfortran/m4/matmul.m4
index f488f5ed38eb0492ea936e3b656e722e1cb73ab0..526303c9f3940b6e63c9ef1689985fcd12ff09ba 100644
--- a/libgfortran/m4/matmul.m4
+++ b/libgfortran/m4/matmul.m4
@@ -195,8 +195,8 @@ sinclude(`matmul_asm_'rtype_code`.m4')dnl
       const rtype_name * restrict abase_n;
       rtype_name bbase_yn;
 
-      if (rystride == ycount)
-	memset (dest, 0, (sizeof (rtype_name) * size0((array_t *) retarray)));
+      if (rystride == xcount)
+	memset (dest, 0, (sizeof (rtype_name) * xcount * ycount));
       else
 	{
 	  for (y = 0; y < ycount; y++)