* tree-loop-distribution.c (struct partition): New field recording
[official-gcc.git] / gcc / testsuite / gfortran.dg / vect / pr69882.f90
blobf77e33f11a96a962941781fcc6220d8ef097a7e8
1 ! { dg-additional-options "-Ofast" }
2 ! { dg-additional-options "-mavx" { target avx_runtime } }
4 subroutine foo(a, x)
5 implicit none
7 integer, parameter :: XX=4, YY=26
8 integer, intent(in) :: x
9 real *8, intent(in) :: a(XX,YY)
10 real *8 :: c(XX)
12 integer i, k
14 c = 0
16 do k=x,YY
17 do i=1,2
18 c(i) = max(c(i), a(i,k))
19 end do
20 end do
22 PRINT *, "c=", c
24 IF (c(1) .gt. 0.0) THEN
25 CALL ABORT
26 END IF
28 IF (c(2) .gt. 0.0) THEN
29 CALL ABORT
30 END IF
31 end subroutine foo
33 PROGRAM MAIN
34 real *8 a(4, 26)
36 a = 0
37 a(3,1) = 100.0
38 a(4,1) = 100.0
40 CALL FOO(a, 1)
41 END PROGRAM