[to-be-committed] [RISC-V] Use Zbkb for general 64 bit constants when profitable
[official-gcc.git] / gcc / testsuite / gfortran.dg / inline_matmul_16.f90
blob580cb1ac9393c052f0b3f83c3484cd19d32925ca
1 ! { dg-do run }
2 ! { dg-options "-ffrontend-optimize -fdump-tree-optimized -Wrealloc-lhs -finline-matmul-limit=1000 -O" }
3 ! PR 66094: Check functionality for MATMUL(TRANSPOSE(A),B)) for two-dimensional arrays
4 program main
5 implicit none
6 integer, parameter :: n = 3, m=4, cnt=2
7 real, dimension(cnt,n) :: a
8 real, dimension(cnt,m) :: b
9 real, dimension(n,m) :: c, cres
10 real, dimension(:,:), allocatable :: calloc
11 integer :: in, im, icnt
13 data a / 2., -3., 5., -7., 11., -13./
14 data b /17., -23., 29., -31., 37., -39., 41., -47./
15 data cres /103., 246., 486., 151., 362., 722., &
16 191., 458., 914., 223., 534., 1062./
18 c = matmul(transpose(a),b)
19 if (sum(c-cres)>1e-4) STOP 1
20 if (sum(c-cres)>1e-4) STOP 2
22 ! Unallocated
23 calloc = matmul(transpose(a),b) ! { dg-warning "Code for reallocating the allocatable array" }
24 if (any(shape(c) /= shape(calloc))) STOP 3
25 if (sum(calloc-cres)>1e-4) STOP 4
26 deallocate(calloc)
28 ! Allocated to wrong shape
29 allocate (calloc(10,10))
30 calloc = matmul(transpose(a),b) ! { dg-warning "Code for reallocating the allocatable array" }
31 if (any(shape(c) /= shape(calloc))) STOP 5
32 if (sum(calloc-cres)>1e-4) STOP 6
33 deallocate(calloc)
35 ! cycle through a few test cases...
36 do in=2,10
37 do im = 2,10
38 do icnt = 2,10
39 block
40 real, dimension(icnt,in) :: a2
41 real, dimension(icnt,im) :: b2
42 real, dimension(in,im) :: c2,cr
43 integer :: i,j,k
44 call random_number(a2)
45 call random_number(b2)
46 c2 = 0
47 do i=1,size(a2,2)
48 do j=1, size(b2,2)
49 do k=1, size(a2,1)
50 c2(i,j) = c2(i,j) + a2(k,i) * b2(k,j)
51 end do
52 end do
53 end do
54 cr = matmul(transpose(a2), b2)
55 if (any(abs(c2-cr) > 1e-4)) STOP 7
56 end block
57 end do
58 end do
59 end do
60 end program main
61 ! { dg-final { scan-tree-dump-times "_gfortran_matmul" 1 "optimized" } }