annotate gcc/testsuite/gfortran.dg/inline_matmul_16.f90 @ 158:494b0b89df80 default tip

...
author Shinji KONO <kono@ie.u-ryukyu.ac.jp>
date Mon, 25 May 2020 18:13:55 +0900
parents 84e7813d76e9
children
Ignore whitespace changes - Everywhere: Within whitespace: At end of lines:
rev   line source
111
kono
parents:
diff changeset
1 ! { dg-do run }
kono
parents:
diff changeset
2 ! { dg-options "-ffrontend-optimize -fdump-tree-optimized -Wrealloc-lhs -finline-matmul-limit=1000 -O" }
kono
parents:
diff changeset
3 ! PR 66094: Check functionality for MATMUL(TRANSPOSE(A),B)) for two-dimensional arrays
kono
parents:
diff changeset
4 program main
kono
parents:
diff changeset
5 implicit none
kono
parents:
diff changeset
6 integer, parameter :: n = 3, m=4, cnt=2
kono
parents:
diff changeset
7 real, dimension(cnt,n) :: a
kono
parents:
diff changeset
8 real, dimension(cnt,m) :: b
kono
parents:
diff changeset
9 real, dimension(n,m) :: c, cres
kono
parents:
diff changeset
10 real, dimension(:,:), allocatable :: calloc
kono
parents:
diff changeset
11 integer :: in, im, icnt
kono
parents:
diff changeset
12
kono
parents:
diff changeset
13 data a / 2., -3., 5., -7., 11., -13./
kono
parents:
diff changeset
14 data b /17., -23., 29., -31., 37., -39., 41., -47./
kono
parents:
diff changeset
15 data cres /103., 246., 486., 151., 362., 722., &
kono
parents:
diff changeset
16 191., 458., 914., 223., 534., 1062./
kono
parents:
diff changeset
17
kono
parents:
diff changeset
18 c = matmul(transpose(a),b)
131
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
19 if (sum(c-cres)>1e-4) STOP 1
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
20 if (sum(c-cres)>1e-4) STOP 2
111
kono
parents:
diff changeset
21
kono
parents:
diff changeset
22 ! Unallocated
kono
parents:
diff changeset
23 calloc = matmul(transpose(a),b) ! { dg-warning "Code for reallocating the allocatable array" }
131
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
24 if (any(shape(c) /= shape(calloc))) STOP 3
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
25 if (sum(calloc-cres)>1e-4) STOP 4
111
kono
parents:
diff changeset
26 deallocate(calloc)
kono
parents:
diff changeset
27
kono
parents:
diff changeset
28 ! Allocated to wrong shape
kono
parents:
diff changeset
29 allocate (calloc(10,10))
kono
parents:
diff changeset
30 calloc = matmul(transpose(a),b) ! { dg-warning "Code for reallocating the allocatable array" }
131
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
31 if (any(shape(c) /= shape(calloc))) STOP 5
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
32 if (sum(calloc-cres)>1e-4) STOP 6
111
kono
parents:
diff changeset
33 deallocate(calloc)
kono
parents:
diff changeset
34
kono
parents:
diff changeset
35 ! cycle through a few test cases...
kono
parents:
diff changeset
36 do in=2,10
kono
parents:
diff changeset
37 do im = 2,10
kono
parents:
diff changeset
38 do icnt = 2,10
kono
parents:
diff changeset
39 block
kono
parents:
diff changeset
40 real, dimension(icnt,in) :: a2
kono
parents:
diff changeset
41 real, dimension(icnt,im) :: b2
kono
parents:
diff changeset
42 real, dimension(in,im) :: c2,cr
kono
parents:
diff changeset
43 integer :: i,j,k
kono
parents:
diff changeset
44 call random_number(a2)
kono
parents:
diff changeset
45 call random_number(b2)
kono
parents:
diff changeset
46 c2 = 0
kono
parents:
diff changeset
47 do i=1,size(a2,2)
kono
parents:
diff changeset
48 do j=1, size(b2,2)
kono
parents:
diff changeset
49 do k=1, size(a2,1)
kono
parents:
diff changeset
50 c2(i,j) = c2(i,j) + a2(k,i) * b2(k,j)
kono
parents:
diff changeset
51 end do
kono
parents:
diff changeset
52 end do
kono
parents:
diff changeset
53 end do
kono
parents:
diff changeset
54 cr = matmul(transpose(a2), b2)
131
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
55 if (any(abs(c2-cr) > 1e-4)) STOP 7
111
kono
parents:
diff changeset
56 end block
kono
parents:
diff changeset
57 end do
kono
parents:
diff changeset
58 end do
kono
parents:
diff changeset
59 end do
kono
parents:
diff changeset
60 end program main
131
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
61 ! { dg-final { scan-tree-dump-times "_gfortran_matmul" 1 "optimized" } }