Fix ifunc detection in target-supports.exp file.
[official-gcc.git] / libgomp / testsuite / libgomp.fortran / simd7.f90
blobb0473faa9e5719e2f5b7c01aaf586805042ae7eb
1 ! { dg-do run }
2 ! { dg-additional-options "-msse2" { target sse2_runtime } }
3 ! { dg-additional-options "-mavx" { target avx_runtime } }
5 subroutine foo (d, e, f, g, m, n)
6 integer :: i, j, b(2:9), c(3:n), d(:), e(2:n), f(2:,3:), n
7 integer, allocatable :: g(:), h(:), k, m
8 logical :: l
9 l = .false.
10 allocate (h(2:7))
11 i = 4; j = 4; b = 7; c = 8; d = 9; e = 10; f = 11; g = 12; h = 13; k = 14; m = 15
12 !$omp simd linear(b)linear(c:2)linear(d:3)linear(e:4)linear(f:5)linear(g:6) &
13 !$omp & linear(h:7)linear(k:8)linear(m:9) reduction(.or.:l)
14 do i = 0, 63
15 l = l .or. .not.allocated (g) .or. .not.allocated (h)
16 l = l .or. .not.allocated (k) .or. .not.allocated (m)
17 l = l .or. any (b /= 7 + i) .or. any (c /= 8 + 2 * i)
18 l = l .or. any (d /= 9 + 3 * i) .or. any (e /= 10 + 4 * i)
19 l = l .or. any (f /= 11 + 5 * i) .or. any (g /= 12 + 6 * i)
20 l = l .or. any (h /= 13 + 7 * i) .or. (k /= 14 + 8 * i)
21 l = l .or. (m /= 15 + 9 * i)
22 l = l .or. (lbound (b, 1) /= 2) .or. (ubound (b, 1) /= 9)
23 l = l .or. (lbound (c, 1) /= 3) .or. (ubound (c, 1) /= n)
24 l = l .or. (lbound (d, 1) /= 1) .or. (ubound (d, 1) /= 17)
25 l = l .or. (lbound (e, 1) /= 2) .or. (ubound (e, 1) /= n)
26 l = l .or. (lbound (f, 1) /= 2) .or. (ubound (f, 1) /= 3)
27 l = l .or. (lbound (f, 2) /= 3) .or. (ubound (f, 2) /= 5)
28 l = l .or. (lbound (g, 1) /= 7) .or. (ubound (g, 1) /= 10)
29 l = l .or. (lbound (h, 1) /= 2) .or. (ubound (h, 1) /= 7)
30 b = b + 1; c = c + 2; d = d + 3; e = e + 4; f = f + 5; g = g + 6
31 h = h + 7; k = k + 8; m = m + 9
32 end do
33 if (l .or. i /= 64) call abort
34 if (any (b /= 7 + 64) .or. any (c /= 8 + 2 * 64)) call abort
35 if (any (d /= 9 + 3 * 64) .or. any (e /= 10 + 4 * 64)) call abort
36 if (any (f /= 11 + 5 * 64) .or. any (g /= 12 + 6 * 64)) call abort
37 if (any (h /= 13 + 7 * 64) .or. (k /= 14 + 8 * 64)) call abort
38 if (m /= 15 + 9 * 64) call abort
39 if ((lbound (b, 1) /= 2) .or. (ubound (b, 1) /= 9)) call abort
40 if ((lbound (c, 1) /= 3) .or. (ubound (c, 1) /= n)) call abort
41 if ((lbound (d, 1) /= 1) .or. (ubound (d, 1) /= 17)) call abort
42 if ((lbound (e, 1) /= 2) .or. (ubound (e, 1) /= n)) call abort
43 if ((lbound (f, 1) /= 2) .or. (ubound (f, 1) /= 3)) call abort
44 if ((lbound (f, 2) /= 3) .or. (ubound (f, 2) /= 5)) call abort
45 if ((lbound (g, 1) /= 7) .or. (ubound (g, 1) /= 10)) call abort
46 if ((lbound (h, 1) /= 2) .or. (ubound (h, 1) /= 7)) call abort
47 i = 4; j = 4; b = 7; c = 8; d = 9; e = 10; f = 11; g = 12; h = 13; k = 14; m = 15
48 !$omp simd linear(b)linear(c:2)linear(d:3)linear(e:4)linear(f:5)linear(g:6) &
49 !$omp & linear(h:7)linear(k:8)linear(m:9) reduction(.or.:l) collapse(2)
50 do i = 0, 7
51 do j = 0, 7
52 l = l .or. .not.allocated (g) .or. .not.allocated (h)
53 l = l .or. .not.allocated (k) .or. .not.allocated (m)
54 l = l .or. any (b /= 7 + (8 * i + j)) .or. any (c /= 8 + 2 * (8 * i + j))
55 l = l .or. any (d /= 9 + 3 * (8 * i + j)) .or. any (e /= 10 + 4 * (8 * i + j))
56 l = l .or. any (f /= 11 + 5 * (8 * i + j)) .or. any (g /= 12 + 6 * (8 * i + j))
57 l = l .or. any (h /= 13 + 7 * (8 * i + j)) .or. (k /= 14 + 8 * (8 * i + j))
58 l = l .or. (m /= 15 + 9 * (8 * i + j))
59 l = l .or. (lbound (b, 1) /= 2) .or. (ubound (b, 1) /= 9)
60 l = l .or. (lbound (c, 1) /= 3) .or. (ubound (c, 1) /= n)
61 l = l .or. (lbound (d, 1) /= 1) .or. (ubound (d, 1) /= 17)
62 l = l .or. (lbound (e, 1) /= 2) .or. (ubound (e, 1) /= n)
63 l = l .or. (lbound (f, 1) /= 2) .or. (ubound (f, 1) /= 3)
64 l = l .or. (lbound (f, 2) /= 3) .or. (ubound (f, 2) /= 5)
65 l = l .or. (lbound (g, 1) /= 7) .or. (ubound (g, 1) /= 10)
66 l = l .or. (lbound (h, 1) /= 2) .or. (ubound (h, 1) /= 7)
67 b = b + 1; c = c + 2; d = d + 3; e = e + 4; f = f + 5; g = g + 6
68 h = h + 7; k = k + 8; m = m + 9
69 end do
70 end do
71 if (l .or. i /= 8 .or. j /= 8) call abort
72 if (any (b /= 7 + 64) .or. any (c /= 8 + 2 * 64)) call abort
73 if (any (d /= 9 + 3 * 64) .or. any (e /= 10 + 4 * 64)) call abort
74 if (any (f /= 11 + 5 * 64) .or. any (g /= 12 + 6 * 64)) call abort
75 if (any (h /= 13 + 7 * 64) .or. (k /= 14 + 8 * 64)) call abort
76 if (m /= 15 + 9 * 64) call abort
77 if ((lbound (b, 1) /= 2) .or. (ubound (b, 1) /= 9)) call abort
78 if ((lbound (c, 1) /= 3) .or. (ubound (c, 1) /= n)) call abort
79 if ((lbound (d, 1) /= 1) .or. (ubound (d, 1) /= 17)) call abort
80 if ((lbound (e, 1) /= 2) .or. (ubound (e, 1) /= n)) call abort
81 if ((lbound (f, 1) /= 2) .or. (ubound (f, 1) /= 3)) call abort
82 if ((lbound (f, 2) /= 3) .or. (ubound (f, 2) /= 5)) call abort
83 if ((lbound (g, 1) /= 7) .or. (ubound (g, 1) /= 10)) call abort
84 if ((lbound (h, 1) /= 2) .or. (ubound (h, 1) /= 7)) call abort
85 i = 4; j = 4; b = 7; c = 8; d = 9; e = 10; f = 11; g = 12; h = 13; k = 14; m = 15
86 !$omp parallel do simd linear(b)linear(c:2)linear(d:3)linear(e:4)linear(f:5) &
87 !$omp & linear(g:6)linear(h:7)linear(k:8)linear(m:9) reduction(.or.:l)
88 do i = 0, 63
89 l = l .or. .not.allocated (g) .or. .not.allocated (h)
90 l = l .or. .not.allocated (k) .or. .not.allocated (m)
91 l = l .or. any (b /= 7 + i) .or. any (c /= 8 + 2 * i)
92 l = l .or. any (d /= 9 + 3 * i) .or. any (e /= 10 + 4 * i)
93 l = l .or. any (f /= 11 + 5 * i) .or. any (g /= 12 + 6 * i)
94 l = l .or. any (h /= 13 + 7 * i) .or. (k /= 14 + 8 * i)
95 l = l .or. (m /= 15 + 9 * i)
96 l = l .or. (lbound (b, 1) /= 2) .or. (ubound (b, 1) /= 9)
97 l = l .or. (lbound (c, 1) /= 3) .or. (ubound (c, 1) /= n)
98 l = l .or. (lbound (d, 1) /= 1) .or. (ubound (d, 1) /= 17)
99 l = l .or. (lbound (e, 1) /= 2) .or. (ubound (e, 1) /= n)
100 l = l .or. (lbound (f, 1) /= 2) .or. (ubound (f, 1) /= 3)
101 l = l .or. (lbound (f, 2) /= 3) .or. (ubound (f, 2) /= 5)
102 l = l .or. (lbound (g, 1) /= 7) .or. (ubound (g, 1) /= 10)
103 l = l .or. (lbound (h, 1) /= 2) .or. (ubound (h, 1) /= 7)
104 b = b + 1; c = c + 2; d = d + 3; e = e + 4; f = f + 5; g = g + 6
105 h = h + 7; k = k + 8; m = m + 9
106 end do
107 if (l .or. i /= 64) call abort
108 if (any (b /= 7 + 64) .or. any (c /= 8 + 2 * 64)) call abort
109 if (any (d /= 9 + 3 * 64) .or. any (e /= 10 + 4 * 64)) call abort
110 if (any (f /= 11 + 5 * 64) .or. any (g /= 12 + 6 * 64)) call abort
111 if (any (h /= 13 + 7 * 64) .or. (k /= 14 + 8 * 64)) call abort
112 if (m /= 15 + 9 * 64) call abort
113 if ((lbound (b, 1) /= 2) .or. (ubound (b, 1) /= 9)) call abort
114 if ((lbound (c, 1) /= 3) .or. (ubound (c, 1) /= n)) call abort
115 if ((lbound (d, 1) /= 1) .or. (ubound (d, 1) /= 17)) call abort
116 if ((lbound (e, 1) /= 2) .or. (ubound (e, 1) /= n)) call abort
117 if ((lbound (f, 1) /= 2) .or. (ubound (f, 1) /= 3)) call abort
118 if ((lbound (f, 2) /= 3) .or. (ubound (f, 2) /= 5)) call abort
119 if ((lbound (g, 1) /= 7) .or. (ubound (g, 1) /= 10)) call abort
120 if ((lbound (h, 1) /= 2) .or. (ubound (h, 1) /= 7)) call abort
121 i = 4; j = 4; b = 7; c = 8; d = 9; e = 10; f = 11; g = 12; h = 13; k = 14; m = 15
122 !$omp parallel do simd linear(b)linear(c:2)linear(d:3)linear(e:4)linear(f:5) &
123 !$omp & linear(g:6)linear(h:7)linear(k:8)linear(m:9) reduction(.or.:l) collapse(2)
124 do i = 0, 7
125 do j = 0, 7
126 l = l .or. .not.allocated (g) .or. .not.allocated (h)
127 l = l .or. .not.allocated (k) .or. .not.allocated (m)
128 l = l .or. any (b /= 7 + (8 * i + j)) .or. any (c /= 8 + 2 * (8 * i + j))
129 l = l .or. any (d /= 9 + 3 * (8 * i + j)) .or. any (e /= 10 + 4 * (8 * i + j))
130 l = l .or. any (f /= 11 + 5 * (8 * i + j)) .or. any (g /= 12 + 6 * (8 * i + j))
131 l = l .or. any (h /= 13 + 7 * (8 * i + j)) .or. (k /= 14 + 8 * (8 * i + j))
132 l = l .or. (m /= 15 + 9 * (8 * i + j))
133 l = l .or. (lbound (b, 1) /= 2) .or. (ubound (b, 1) /= 9)
134 l = l .or. (lbound (c, 1) /= 3) .or. (ubound (c, 1) /= n)
135 l = l .or. (lbound (d, 1) /= 1) .or. (ubound (d, 1) /= 17)
136 l = l .or. (lbound (e, 1) /= 2) .or. (ubound (e, 1) /= n)
137 l = l .or. (lbound (f, 1) /= 2) .or. (ubound (f, 1) /= 3)
138 l = l .or. (lbound (f, 2) /= 3) .or. (ubound (f, 2) /= 5)
139 l = l .or. (lbound (g, 1) /= 7) .or. (ubound (g, 1) /= 10)
140 l = l .or. (lbound (h, 1) /= 2) .or. (ubound (h, 1) /= 7)
141 b = b + 1; c = c + 2; d = d + 3; e = e + 4; f = f + 5; g = g + 6
142 h = h + 7; k = k + 8; m = m + 9
143 end do
144 end do
145 if (l .or. i /= 8 .or. j /= 8) call abort
146 if (any (b /= 7 + 64) .or. any (c /= 8 + 2 * 64)) call abort
147 if (any (d /= 9 + 3 * 64) .or. any (e /= 10 + 4 * 64)) call abort
148 if (any (f /= 11 + 5 * 64) .or. any (g /= 12 + 6 * 64)) call abort
149 if (any (h /= 13 + 7 * 64) .or. (k /= 14 + 8 * 64)) call abort
150 if (m /= 15 + 9 * 64) call abort
151 if ((lbound (b, 1) /= 2) .or. (ubound (b, 1) /= 9)) call abort
152 if ((lbound (c, 1) /= 3) .or. (ubound (c, 1) /= n)) call abort
153 if ((lbound (d, 1) /= 1) .or. (ubound (d, 1) /= 17)) call abort
154 if ((lbound (e, 1) /= 2) .or. (ubound (e, 1) /= n)) call abort
155 if ((lbound (f, 1) /= 2) .or. (ubound (f, 1) /= 3)) call abort
156 if ((lbound (f, 2) /= 3) .or. (ubound (f, 2) /= 5)) call abort
157 if ((lbound (g, 1) /= 7) .or. (ubound (g, 1) /= 10)) call abort
158 if ((lbound (h, 1) /= 2) .or. (ubound (h, 1) /= 7)) call abort
159 end subroutine
161 interface
162 subroutine foo (d, e, f, g, m, n)
163 integer :: d(:), e(2:n), f(2:,3:), n
164 integer, allocatable :: g(:), m
165 end subroutine
166 end interface
167 integer, parameter :: n = 8
168 integer :: d(2:18), e(3:n+1), f(5:6,7:9)
169 integer, allocatable :: g(:), m
170 allocate (g(7:10))
171 call foo (d, e, f, g, m, n)