Commit 86e03ef9 by Thomas Koenig

re PR fortran/81974 (ICE verify_gimple failed type mismatch in binary expression)

2017-08-27  Thomas Koenig  <tkoenig@gcc.gnu.org>

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

2017-08-27  Thomas Koenig  <tkoenig@gcc.gnu.org>

	PR fortran/81974
	* gfortran.dg/inline_matmul_19.f90:  New test.

From-SVN: r251368
parent 3e7b89ac
2017-08-27 Thomas Koenig <tkoenig@gcc.gnu.org>
PR fortran/81974
* frontend-passes (inline_matumul_assign): Explicity
set typespec for call to CONJG.
2017-08-21 Jerry DeLisle <jvdelisle@gcc.gnu.org>
PR fortran/81296
......
......@@ -3837,14 +3837,25 @@ inline_matmul_assign (gfc_code **c, int *walk_subtrees,
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;
......
2017-08-27 Thomas Koenig <tkoenig@gcc.gnu.org>
PR fortran/81974
* gfortran.dg/inline_matmul_19.f90: New test.
2017-08-25 Steven Munroe <munroesj@gcc.gnu.org>
* gcc.target/powerpc/m128-check.h: New file.
......
! { 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
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment