lto: Remove random_seed from section name.
[official-gcc.git] / gcc / testsuite / gfortran.dg / matmul_10.f90
bloba4a2589796fce41b9d68f05807b2289d162ad86e
1 ! { dg-do run }
2 ! { dg-options "-Warray-temporaries" }
3 ! PR 71961 - no array temporary was created.
4 ! Original test case by Joost VandeVondele
5 program main
6 implicit none
7 integer :: i
8 integer, dimension(:,:), pointer :: a
9 integer, dimension(:,:), allocatable :: b
10 ALLOCATE(a(4,4),b(4,2))
11 a=1 ; b=2
12 a(:,1:2)=matmul(a(:,1:4),b(:,:)) ! { dg-warning "Creating array temporary" }
13 if (any(a /= reshape((/8,8,8,8,8,8,8,8,1,1,1,1,1,1,1,1/),(/4,4/)))) &
14 STOP 1
15 a = reshape([((-1**i)*i,i=1,16)],[4,4])
16 b = reshape([((-1**(i-1))*i**2,i=1,8)],[4,2])
17 b(1:2,1:2) = matmul(a(1:2,:),b) ! { dg-warning "Creating array temporary" }
18 if (any(b /= reshape([310, 340, -9, -16, 1478, 1652, -49, -64],[4,2]))) &
19 STOP 2
20 deallocate(a)
21 deallocate(b)
22 end program main