PR inline-asm/84742
[official-gcc.git] / gcc / testsuite / gfortran.dg / inline_matmul_14.f90
blob2272b4084b0ceb1e6f688c4df1224c2345afe9dd
1 ! { dg-do run }
2 ! { dg-options "-O -ffrontend-optimize -fdump-tree-optimized" }
3 ! PR 79930 - missed optimization by not inlining matmul in expressions.
5 module foo
6 implicit none
7 contains
8 subroutine test1
9 ! Test with fixed dimensions
10 real, dimension(3,2) :: a1
11 real, dimension(2,4) :: b1
12 real, dimension(3,4) :: cres1
13 real, dimension(3,3) :: a2
14 real, dimension(3) :: v1, v2
15 real :: r
16 character(len=9*18) :: r1, r2
17 real(kind=8), dimension(3,3) :: a3, b3, c3, d3, res3
19 data a1 / 2., -3., 5., -7., 11., -13./
20 data b1 /17., -23., 29., -31., 37., -39., 41., -47./
21 data cres1 /195., -304., 384., 275., -428., 548., 347., -540., 692., 411., -640., 816./
23 data a2 / 2., -3., 5., -7., 11., -13., 17., -23., 29./
24 data v1 /-31., 37., -41./
25 data v2 /43., -47., 53./
27 data a3/-2.d0, 3.d0, 5.d0, -7.d0, -11.d0, 13.d0, 17.d0, -19.d0, -23.d0/
28 data b3/29.d0, -31.d0, 37.d0, -41.d0, 43.d0, -47.d0, 53.d0, -59.d0, 61.d0/
29 data c3/-67.d0,71.d0, 73.d0, -79.d0, -83.d0, 89.d0, 97.d0, -101.d0, 103.d0/
30 data d3/107.d0, 109.d0, 113.d0, 127.d0, 131.d0, 137.d0, 139.d0, 149.d0, 151.d0/
31 data res3/48476106.d0, -12727087.d0, -68646789.d0, 58682206.d0, -15428737.d0, -83096539.d0,&
32 & 65359710.d0, -17176589.d0, -92551887.d0/
34 write (unit=r1, fmt='(12F12.5)') matmul(a1,b1)
35 write (unit=r2, fmt='(12F12.5)') cres1
36 if (r1 /= r2) STOP 1
38 r = dot_product(matmul(a2,v1),v2)
39 if (abs(r+208320) > 1) STOP 2
41 write (unit=r1,fmt='(1P,9E18.10)') matmul(matmul(a3,b3),matmul(c3,d3))
42 write (unit=r2,fmt='(1P,9E18.10)') res3
43 if (r1 /= r2) STOP 3
45 end subroutine test1
47 subroutine test2
48 ! Test with dimensions not known at compile-time
49 real, dimension(:,:), allocatable :: a1
50 real, dimension(:,:), allocatable :: b1
51 real, dimension(3,4) :: cres1
52 real, dimension(:,:), allocatable :: a2
53 real, dimension(:), allocatable :: v1, v2
54 real :: r
55 character(len=9*18) :: r1, r2
56 real(kind=8), dimension(3,3) :: a3, b3, c3, d3, res3
57 data cres1 /195., -304., 384., 275., -428., 548., 347., -540., 692., 411., -640., 816./
58 data res3/48476106.d0, -12727087.d0, -68646789.d0, 58682206.d0, -15428737.d0, -83096539.d0,&
59 & 65359710.d0, -17176589.d0, -92551887.d0/
61 a1 = reshape([ 2., -3., 5., -7., 11., -13.], [3,2])
62 b1 = reshape([17., -23., 29., -31., 37., -39., 41., -47.],[2,4])
64 a2 = reshape([2., -3., 5., -7., 11., -13., 17., -23., 29.],[3,3]);
65 v1 = [-31., 37., -41.]
66 v2 = [43., -47., 53.]
68 a3 = reshape([-2.d0, 3.d0, 5.d0, -7.d0, -11.d0, 13.d0, 17.d0, -19.d0, -23.d0], [3,3])
69 b3 = reshape([29.d0, -31.d0, 37.d0, -41.d0, 43.d0, -47.d0, 53.d0, -59.d0, 61.d0], [3,3])
70 c3 = reshape([-67.d0,71.d0, 73.d0, -79.d0, -83.d0, 89.d0, 97.d0, -101.d0, 103.d0], [3,3])
71 d3 = reshape([107.d0, 109.d0, 113.d0, 127.d0, 131.d0, 137.d0, 139.d0, 149.d0, 151.d0],[3,3])
73 write (unit=r1, fmt='(12F12.5)') matmul(a1,b1)
74 write (unit=r2, fmt='(12F12.5)') cres1
75 if (r1 /= r2) STOP 4
77 r = dot_product(matmul(a2,v1),v2)
78 if (abs(r+208320) > 1) STOP 5
80 write (unit=r1,fmt='(1P,9E18.10)') matmul(matmul(a3,b3),matmul(c3,d3))
81 write (unit=r2,fmt='(1P,9E18.10)') res3
82 if (r1 /= r2) STOP 6
84 end subroutine test2
86 end module foo
88 program main
89 use foo
90 implicit none
91 call test1
92 call test2
93 ! call test3
94 end program main
95 ! { dg-final { scan-tree-dump-times "_gfortran_matmul" 0 "optimized" } }