c: Fix up pointer types to may_alias structures [PR114493]
[official-gcc.git] / gcc / testsuite / gfortran.dg / minmaxloc_zerosize_1.f90
blob94e5d00b0641e64156cfc9397f50eb91bddca9be
1 ! { dg-do run }
2 ! { dg-additional-options "-fdump-tree-original" }
3 program main
4 implicit none
5 integer, parameter :: z(0) = 0
6 integer, parameter, dimension(1) :: a = minloc(z)
7 integer, parameter, dimension(1) :: b = minloc(z,mask=z>0)
8 integer, parameter :: c = minloc(z,dim=1)
10 integer, parameter, dimension(1) :: d = maxloc(z)
11 integer, parameter, dimension(1) :: e = maxloc(z,mask=z>0)
12 integer, parameter :: f = maxloc(z,dim=1)
14 character(len=12) line
16 if (a(1) /= 0) stop 1
17 if (b(1) /= 0) stop 2
18 if (c /= 0) stop 3
20 if (d(1) /= 0) stop 4
21 if (e(1) /= 0) stop 5
22 if (f /= 0) stop 6
24 write (unit=line,fmt='(6I2)') minloc(z), minloc(z,mask=z>0), minloc(z,dim=1), &
25 maxloc(z), maxloc(z,mask=z<0), maxloc(z,dim=1)
26 if (line /= ' 0 0 0 0 0 0') stop 7
27 end program main
28 ! { dg-final { scan-tree-dump-times "_gfortran_stop" 1 "original" } }