* tree-loop-distribution.c (struct partition): New field recording
[official-gcc.git] / gcc / testsuite / gfortran.dg / minmaxloc_7.f90
blob2645a96e444b7c418d9595badc1236c0ac1fb337
1 ! Contributed by Tobias Burnus <burnus@gcc.gnu.org>
2 ! { dg-do run }
3 program test
4 implicit none
5 real, volatile, allocatable :: A(:)
6 logical, volatile :: mask(11)
8 A = [1,2,3,5,6,1,35,3,7,-3,-47]
9 mask = .true.
10 mask(7) = .false.
11 mask(11) = .false.
12 call sub2 (minloc(A),11)
13 call sub2 (maxloc(A, mask=mask),9)
14 A = minloc(A)
15 if (size (A) /= 1 .or. A(1) /= 11) call abort ()
16 contains
17 subroutine sub2(A,n)
18 integer :: A(:),n
19 if (A(1) /= n .or. size (A) /= 1) call abort ()
20 end subroutine sub2
21 end program test