tree-optimization/113385 - wrong loop father with early exit vectorization
[official-gcc.git] / gcc / testsuite / gfortran.dg / gomp / openmp-simd-1.f90
blob4765586982d1a65eba21adfb8aab38cbc9ce5c29
1 ! { dg-do compile }
2 ! { dg-options "-fno-openmp -fopenmp-simd -fdump-tree-original -O2" }
4 !$omp declare reduction (foo:integer:omp_out = omp_out + omp_in)
5 interface
6 integer function foo (x, y)
7 integer, value :: x, y
8 !$omp declare simd (foo) linear (y : 2)
9 end function foo
10 end interface
11 integer :: i, a(64), b, c
12 integer, save :: d
13 !$omp threadprivate (d)
14 d = 5
15 a = 6
16 !$omp simd
17 do i = 1, 64
18 a(i) = foo (a(i), 2 * i)
19 end do
20 b = 0
21 c = 0
22 !$omp simd reduction (+:b) reduction (foo:c)
23 do i = 1, 64
24 b = b + a(i)
25 c = c + a(i) * 2
26 end do
27 print *, b
28 b = 0
29 !$omp parallel
30 !$omp do simd schedule(static, 4) safelen (8) reduction (+:b)
31 do i = 1, 64
32 a(i) = a(i) + 1
33 b = b + 1
34 end do
35 !$omp end parallel
36 print *, b
37 b = 0
38 !$omp parallel do simd schedule(static, 4) safelen (8) &
39 !$omp num_threads (4) if (.true.) reduction (+:b)
40 do i = 1, 64
41 a(i) = a(i) + 1
42 b = b + 1
43 end do
44 print *, b
45 b = 0
46 !$omp parallel
47 !$omp do simd schedule(static, 4) safelen (8) reduction (+:b)
48 do i = 1, 64
49 a(i) = a(i) + 1
50 b = b + 1
51 end do
52 !$omp enddosimd
53 !$omp end parallel
54 print *, b
55 b = 0
56 !$omp parallel do simd schedule(static, 4) safelen (8) &
57 !$omp num_threads (4) if (.true.) reduction (+:b)
58 do i = 1, 64
59 a(i) = a(i) + 1
60 b = b + 1
61 end do
62 !$omp end parallel do simd
63 !$omp atomic seq_cst
64 b = b + 1
65 !$omp end atomic
66 !$omp barrier
67 !$omp parallel private (i)
68 !$omp cancellation point parallel
69 !$omp critical (bar)
70 b = b + 1
71 !$omp end critical (bar)
72 !$omp flush(b)
73 !$omp single
74 b = b + 1
75 !$omp end single
76 !$omp do ordered
77 do i = 1, 10
78 !$omp atomic
79 b = b + 1
80 !$omp end atomic
81 !$omp ordered
82 print *, b
83 !$omp end ordered
84 end do
85 !$omp end do
86 !$omp master
87 b = b + 1
88 !$omp end master
89 !$omp cancel parallel
90 !$omp end parallel
91 !$omp parallel do schedule(runtime) num_threads(8)
92 do i = 1, 10
93 print *, b
94 end do
95 !$omp end parallel do
96 !$omp sections
97 !$omp section
98 b = b + 1
99 !$omp section
100 c = c + 1
101 !$omp end sections
102 print *, b
103 !$omp parallel sections firstprivate (b) if (.true.)
104 !$omp section
105 b = b + 1
106 !$omp section
107 c = c + 1
108 !$omp endparallelsections
109 !$omp workshare
110 b = 24
111 !$omp end workshare
112 !$omp parallel workshare num_threads (2)
113 b = b + 1
114 c = c + 1
115 !$omp end parallel workshare
116 print *, b
117 !$omp parallel
118 !$omp single
119 !$omp taskgroup
120 !$omp task firstprivate (b)
121 b = b + 1
122 !$omp taskyield
123 !$omp end task
124 !$omp task firstprivate (b)
125 b = b + 1
126 !$omp end task
127 !$omp taskwait
128 !$omp end taskgroup
129 !$omp end single
130 !$omp end parallel
131 print *, a, c
134 ! { dg-final { scan-tree-dump-times "pragma omp simd" 6 "original" } }
135 ! { dg-final { scan-tree-dump-times "pragma omp" 6 "original" } }
136 ! { dg-final { scan-tree-dump-times "__builtin_GOMP" 0 "original" } }