view gcc/testsuite/gfortran.dg/inline_matmul_10.f90 @ 152:2b5abeee2509

update gcc11
author anatofuz
date Mon, 25 May 2020 07:50:57 +0900
parents 84e7813d76e9
children
line wrap: on
line source

! { dg-do  run }
! { dg-options "-ffrontend-optimize" }
! PR 66111 - this used to ICE with matmul inlining.
! Original test case by Mikael Morin.

implicit none
  integer, parameter :: n = 4
  integer, dimension(n, n) :: a, b, c
  integer, dimension(n*n)  :: p, res, res2
  integer, dimension(n)    :: v

  integer :: i

  p = [ +59, -53, +47, -43, &
        -37, +31, -29, +23, &
        +19, -17, +13, -11, &
        - 7, + 5, - 3, + 2  ]
  a = reshape(p, shape(a))
  b = reshape([(i, i=1, size(a))], shape(b))
  v = [ 3, 1, 2, 4]
  c = matmul(a, b)
  res = [ + 14, - 22, + 16, - 22, &
          +150, -158, +128, -138, &
          +286, -294, +240, -254, &
          +422, -430, +352, -370  ]
  !print *,c
  if (any(c /= reshape(res, shape(c)))) STOP 1
  c(:,v) = matmul(a, b)
  if (any(c(:,v) /= reshape(res, shape(c)))) STOP 2
  c(v,:) = matmul(a, b)
  if (any(c(v,:) /= reshape(res, shape(c)))) STOP 3

  c = matmul(a(:,v),b(v,:))
  if (any(c /= reshape(res, shape(c)))) STOP 4
end