AArch64: correct constraint on Upl early clobber alternatives
[official-gcc.git] / gcc / testsuite / gfortran.dg / minmaxloc_4.f90
blob753fc51e07296871b9e5d7c9ecdc6735b97bdeba
1 ! { dg-do run }
2 ! Test to make sure that PR 33354 remains fixed and doesn't regress
3 PROGRAM TST
4 IMPLICIT NONE
5 REAL :: A(1,3)
6 A(:,1) = 10
7 A(:,2) = 20
8 A(:,3) = 30
10 !WRITE(*,*) SUM(A(:,1:3),1)
11 !WRITE(*,*) MINLOC(SUM(A(:,1:3),1),1)
12 if (minloc(sum(a(:,1:3),1),1) .ne. 1) STOP 1
13 if (maxloc(sum(a(:,1:3),1),1) .ne. 3) STOP 2
15 END PROGRAM TST