arm: Add .type and .size to __gnu_cmse_nonsecure_call [PR115360]
[official-gcc.git] / gcc / testsuite / gfortran.dg / minmaxloc_13.f90
blob3ebfdc921ec322e6b4fbc4a8355c901c13cf8c04
1 ! { dg-do run }
2 ! Test run-time of MINLOC and MAXLOC with BACK
3 program main
4 implicit none
5 integer:: i1(6)
6 integer:: d1
7 integer:: d2
8 integer:: d3
9 integer:: d4
10 integer:: i2(4,4)
11 integer:: d5(2)
12 integer:: d6(2)
13 integer:: d7(4)
14 integer:: d25(4)
15 integer:: d26(4)
17 integer:: i3(4,4)
18 integer:: d8(4)
19 integer:: i4(4,4)
20 integer:: d9(4)
22 integer:: d10(4)
23 character(len=2) :: c0(9)
24 character(len=2) :: c1(3,3)
25 integer:: d11(2)
26 integer:: d12(2)
27 integer:: d13(2)
28 integer:: d14(2)
29 integer:: d15(3)
30 integer:: d16(3)
31 integer:: d17(3)
32 integer:: d18(3)
33 integer:: d19
34 integer:: d20
35 integer:: d21
36 integer:: d22
37 integer:: d23(3)
38 integer:: d24(3)
40 i1 = [ 1,2,3,1,2,3];
41 d1 = minloc(i1,dim=1,back=.true.)
42 d2 = minloc(i1,dim=1,back=.false.)
43 d3 = maxloc(i1,dim=1,back=.true.)
44 d4 = maxloc(i1,dim=1,back=.false.)
45 i2 = reshape([1,2,1,2,2,3,3,2,3,4,4,3,4,5,5,4], &
46 [4,4]);
47 d5 = minloc(i2,back=.true.)
48 d6 = maxloc(i2,back=.true.)
49 d7= minloc(i2,dim=1,back=.true.)
50 d25 = minloc(i2,dim=2,mask=i2<2,back=.true.)
51 d26 = maxloc(i2,dim=1,mask=i2<3,back=.true.)
53 i3 = transpose(i2)
54 d8 = minloc(i3,dim=2,back=.true.)
55 i4 = reshape([1,2,1,2,2,1,2,1,1,2,1,2,2,1,2,1],&
56 ([4,4]))
57 d9 = minloc(i4,dim=1,mask=i4>1,back=.true.)
59 d10 = maxloc(i4,dim=1,mask=i4>1,back=.true.)
60 c0 = ["aa", "bb", "aa", &
61 "cc", "bb", "cc", "aa", "bb", "aa"]
62 c1 = reshape(c0, [3,3]);
63 d11 = minloc(c1,back=.true.)
64 d12 = maxloc(c1,back=.true.)
65 d13 = minloc(c1,mask=c1>"aa",back=.true.)
66 d14 = maxloc(c1,mask=c1<"cc",back=.true.)
67 d15 = minloc(c1,dim=1,back=.true.)
68 d16 = maxloc(c1,dim=1,back=.true.)
69 d17 = minloc(c1,dim=2,back=.true.)
70 d18 = maxloc(c1,dim=2,back=.true.)
71 d19 = minloc(c0,dim=1,back=.true.)
72 d20 = maxloc(c0,dim=1,back=.true.)
73 d21 = minloc(c0,dim=1,mask=c0>"aa",back=.true.)
74 d22 = maxloc(c0,dim=1,mask=c0<"cc",back=.true.)
75 d23 = minloc(c1,dim=2,mask=c1>"aa",back=.true.)
76 d24 = maxloc(c1,dim=2,mask=c1<"cc",back=.true.)
78 if (d1 /= 4) STOP 2626
79 if (d2 /= 1) STOP 2627
80 if (d3 /= 6) STOP 2628
81 if (d4 /= 3) STOP 2629
82 if (any (d5 /= [3,1])) STOP 2630
83 if (any (d6 /= [3,4])) STOP 2631
84 if (any (d7 /= [3,4,4,4])) STOP 2632
85 if (any (d8 /= d7)) STOP 2633
86 if (any (d9 /= [4,3,4,3])) STOP 2634
87 if (any (d10 /= d9)) STOP 2635
88 if (any(d11 /= [3,3])) STOP 2636
89 if (any(d12 /= [3,2])) STOP 2637
90 if (any(d13 /= [2,3])) STOP 2638
91 if (any(d14 /= [2,3])) STOP 2639
92 if (any(d15 /= [3,2,3])) STOP 2640
93 if (any(d16 /= [2,3,2])) STOP 2641
94 if (any(d17 /= [3,3,3])) STOP 2642
95 if (any(d18 /= [2,3,2])) STOP 2643
96 if (d19 /= 9) STOP 2644
97 if (d20 /= 6) STOP 2645
98 if (d21 /= 8 .or. d22 /= 8) STOP 2646
99 if (any(d23 /= [2,3,2])) STOP 2647
100 if (any(d24 /= 3)) STOP 2648
101 if (any(d25 /= [1,0,1,0])) STOP 2649
102 if (any(d26 /= [4,4,0,0])) STOP 2650
103 end program