Hello world,

to relieve the boredom on the fortran mailing list and to fix
a regression I thought I'd submit a patch :-)

Apparently, a call to CONJG wasn't picking up the right
typespec, which led to an ICE with gimplification later.

Regression-tested.  OK for trunk?

Regards

        Thomas

2017-08-26  Thomas Koenig  <tkoe...@gcc.gnu.org>

        PR fortran/81974
        * frontend-passes (inline_matumul_assign):  Explicity
        set typespec for call to CONJG.

2017-08-26  Thomas Koenig  <tkoe...@gcc.gnu.org>

        PR fortran/81974
        * gfortran.dg/inline_matmul_19.f90:  New test
Index: frontend-passes.c
===================================================================
--- frontend-passes.c	(Revision 251125)
+++ frontend-passes.c	(Arbeitskopie)
@@ -3837,14 +3837,25 @@ inline_matmul_assign (gfc_code **c, int *walk_subt
       gcc_unreachable();
     }
 
+  /* Build the conjg call around the variables.  Set the typespec manually
+     because gfc_build_intrinsic_call sometimes gets this wrong.  */
   if (conjg_a)
-    ascalar = gfc_build_intrinsic_call (ns, GFC_ISYM_CONJG, "conjg",
-					matrix_a->where, 1, ascalar);
+    {
+      gfc_typespec ts;
+      ts = matrix_a->ts;
+      ascalar = gfc_build_intrinsic_call (ns, GFC_ISYM_CONJG, "conjg",
+					  matrix_a->where, 1, ascalar);
+      ascalar->ts = ts;
+    }
 
   if (conjg_b)
-    bscalar = gfc_build_intrinsic_call (ns, GFC_ISYM_CONJG, "conjg",
-					matrix_b->where, 1, bscalar);
-
+    {
+      gfc_typespec ts;
+      ts = matrix_b->ts;
+      bscalar = gfc_build_intrinsic_call (ns, GFC_ISYM_CONJG, "conjg",
+					  matrix_b->where, 1, bscalar);
+      bscalar->ts = ts;
+    }
   /* First loop comes after the zero assignment.  */
   assign_zero->next = do_1;
 
  ! { dg-do  run }
  ! { dg-options "-ffrontend-optimize" }
  ! PR 81974 - this used to cause an ICE.
  
  implicit none
      COMPLEX(kind=kind(0d0)), DIMENSION(3, 3) :: R
      REAL(kind=kind(0d0)), DIMENSION(3, 3)    :: M,a,b
      complex(8), dimension(3,3) :: res, c
      integer :: i, j, k
      c = 0
      call random_number(m)
      call random_number(a)
      call random_number(b)
      r = cmplx(a, b, 8)
      do k=1,3
         do j=1,3
            do i=1,3
               c(k,j) = c(k,j) + conjg(r(i,k)) * m(i,j)
            end do
         end do
      end do
      res = MATMUL(TRANSPOSE(CONJG(R)), M)
      if (any(abs(res-c) >= 1e-6)) call abort
      c = 0
      do k=1,3
         do j=1,3
            do i=1,3
               c(i,k) = c(i,k) + m(i,j) * conjg(r(k,j))
            end do
         end do
      end do
      res = matmul(m, transpose(conjg(r)))
      if (any(abs(res-c) >= 1e-6)) call abort
      END

Reply via email to