AArch64: correct constraint on Upl early clobber alternatives
[official-gcc.git] / gcc / testsuite / gfortran.dg / findloc_3.f90
blobf83c122946eb134001ab6094a6b9c1f155f8f5ee
1 ! { dg-do run }
2 ! Various tests with findloc with character variables.
3 program main
4 character(len=2) :: a(3,3), c(3,3), d(3,4)
5 character(len=3) :: b(3,3)
6 integer :: ret(2)
7 integer :: i,j
8 character(len=3) :: s
9 logical :: lo
10 logical, dimension(3,4) :: msk
11 data a /"11", "21", "31", "12", "22", "32", "13", "23", "33" /
12 data b /"11 ", "21 ", "31 ", "12 ", "22 ", "32 ", "13 ", "23 ", "33 " /
13 if (any(findloc(a,"11 ") /= [1,1])) stop 1
14 ret = findloc(b,"31")
15 do j=1,3
16 do i=1,3
17 write(unit=s,fmt='(2I1," ")') i,j
18 ret = findloc(b,s)
19 if (b(ret(1),ret(2)) /= s) stop 2
20 end do
21 end do
23 if (any(findloc(b(::2,::2),"13") /= [1,2])) stop 3
25 do j=1,3
26 do i=1,3
27 write(unit=c(i,j),fmt='(I2)') 2+i-j
28 end do
29 end do
31 if (any(findloc(c," 1") /= [1,2])) stop 4
32 if (any(findloc(c," 1", back=.true.) /= [2,3])) stop 5
33 if (any(findloc(c," 1", back=.true., mask=.false.) /= [0,0])) stop 6
35 lo = .true.
36 if (any(findloc(c," 2", dim=1) /= [1,2,3])) stop 7
37 if (any(findloc(c," 2",dim=1,mask=lo) /= [1,2,3])) stop 8
39 if (any(findloc(c," 2", dim=1,back=.true.) /= [1,2,3])) stop 9
40 if (any(findloc(c," 2",dim=1,mask=lo,back=.true.) /= [1,2,3])) stop 10
41 do j=1,4
42 do i=1,3
43 if (j<= i) then
44 d(i,j) = "AA"
45 else
46 d(i,j) = "BB"
47 end if
48 end do
49 end do
50 print '(4A3)', transpose(d)
51 if (any(findloc(d,"AA") /= [1,1])) stop 11
52 if (any(findloc(d,"BB") /= [1,2])) stop 12
53 msk = .true.
54 if (any(findloc(d,"AA", mask=msk) /= [1,1])) stop 11
55 if (any(findloc(d,"BB", mask=msk) /= [1,2])) stop 12
56 if (any(findloc(d,"AA", dim=1) /= [1,2,3,0])) stop 13
57 if (any(findloc(d,"BB", dim=1) /= [0,1,1,1])) stop 14
58 if (any(findloc(d,"AA", dim=2) /= [1,1,1])) stop 15
59 if (any(findloc(d,"BB", dim=2) /= [2,3,4])) stop 16
60 if (any(findloc(d,"AA", dim=1,mask=msk) /= [1,2,3,0])) stop 17
61 if (any(findloc(d,"BB", dim=1,mask=msk) /= [0,1,1,1])) stop 18
62 if (any(findloc(d,"AA", dim=2,mask=msk) /= [1,1,1])) stop 19
63 if (any(findloc(d,"BB", dim=2,mask=msk) /= [2,3,4])) stop 20
65 if (any(findloc(d,"AA", dim=1, back=.true.) /= [3,3,3,0])) stop 21
66 if (any(findloc(d,"AA", dim=1, back=.true., mask=msk) /= [3,3,3,0])) stop 22
67 if (any(findloc(d,"BB", dim=2, back=.true.) /= [4,4,4])) stop 23
68 if (any(findloc(d,"BB", dim=2, back=.true.,mask=msk) /= [4,4,4])) stop 24
70 msk(1,:) = .false.
71 print '(4L3)', transpose(msk)
72 if (any(findloc(d,"AA", dim=1,mask=msk) /= [2,2,3,0])) stop 21
73 if (any(findloc(d,"BB", dim=2,mask=msk) /= [0,3,4])) stop 22
74 if (any(findloc(d,"AA", dim=2, mask=msk, back=.true.) /= [0,2,3])) stop 23
75 if (any(findloc(d,"AA", dim=1, mask=msk, back=.true.) /= [3,3,3,0])) stop 24
77 end program main