diff gcc/testsuite/gfortran.dg/inline_matmul_2.f90 @ 111:04ced10e8804

gcc 7
author kono
date Fri, 27 Oct 2017 22:46:09 +0900
parents
children 84e7813d76e9
line wrap: on
line diff
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/gcc/testsuite/gfortran.dg/inline_matmul_2.f90	Fri Oct 27 22:46:09 2017 +0900
@@ -0,0 +1,64 @@
+! { dg-do compile }
+! { dg-options "-ffrontend-optimize -finline-matmul-limit=0 -fdump-tree-original" }
+! PR 37131 - no inlining with -finline-matmul-limit=0
+program main
+  real, dimension(3,2) :: a
+  real, dimension(2,4) :: b
+  real, dimension(3,4) :: c
+  real, dimension(3,4) :: cres
+  real, dimension(:,:), allocatable :: calloc
+  integer :: a1 = size(a,1), a2 = size(a,2)
+  integer :: b1 = size(b,1), b2 = size(b,2)
+  integer :: c1 = size(c,1), c2 = size(c,2)
+
+  data a / 2.,  -3.,  5.,  -7., 11., -13./
+  data b /17., -23., 29., -31., 37., -39., 41., -47./
+  data cres /195., -304.,  384.,  275., -428.,  548.,  347., -540.,  692.,  411., -640.,  816./
+  c = matmul(a,b)
+  if (sum(c-cres)>1e-4) call abort
+
+  calloc = matmul(a,b)
+  if (sum(calloc-cres)>1e-4) call abort
+  if (any([size(calloc,1), size(calloc,2)] /= [3,4])) call abort
+  deallocate(calloc)
+
+  allocate(calloc(4,4))
+  calloc = matmul(a,b)
+  if (sum(calloc-cres)>1e-4) call abort
+  if (any([size(calloc,1), size(calloc,2)] /= [3,4])) call abort
+  deallocate(calloc)
+
+  allocate(calloc(3,3))
+  calloc = matmul(a,b)
+  if (sum(calloc-cres)>1e-4) call abort
+  if (any([size(calloc,1), size(calloc,2)] /= [3,4])) call abort
+  deallocate(calloc)
+  
+  block
+    real :: aa(a1, a2), bb(b1, b2), cc(c1, c2)
+    aa = a
+    bb = b
+
+    cc = matmul(aa,bb)
+    if (sum(cc-cres)>1e-4) call abort
+    calloc = matmul(aa,bb)
+    if (sum(calloc-cres)>1e-4) call abort
+    if (any([size(calloc,1), size(calloc,2)] /= [3,4])) call abort
+    calloc = 42.
+    deallocate(calloc)
+
+    allocate(calloc(4,4))
+    calloc = matmul(aa,bb)
+    if (sum(calloc-cres)>1e-4) call abort
+    if (any([size(calloc,1), size(calloc,2)] /= [3,4])) call abort
+    deallocate(calloc)
+
+    allocate(calloc(3,3))
+    calloc = matmul(aa,bb)
+    if (sum(calloc-cres)>1e-4) call abort
+    if (any([size(calloc,1), size(calloc,2)] /= [3,4])) call abort
+    deallocate(calloc)
+  end block
+
+end program main
+! { dg-final { scan-tree-dump-times "_gfortran_matmul" 8 "original" } }