2 ! { dg-options "-fno-openmp -fopenmp-simd -fdump-tree-original -O2" }
4 !$omp declare reduction (foo:integer:omp_out = omp_out + omp_in)
6 integer function foo (x
, y
)
8 !$omp declare simd (foo) linear (y : 2)
11 integer :: i
, a(64), b
, c
13 !$omp threadprivate (d)
18 a(i
) = foo (a(i
), 2 * i
)
22 !$omp simd reduction (+:b) reduction (foo:c)
30 !$omp do simd schedule(static, 4) safelen (8) reduction (+:b)
38 !$omp parallel do simd schedule(static, 4) safelen (8) &
39 !$omp num_threads (4) if (.true.) reduction (+:b)
47 !$omp do simd schedule(static, 4) safelen (8) reduction (+:b)
56 !$omp parallel do simd schedule(static, 4) safelen (8) &
57 !$omp num_threads (4) if (.true.) reduction (+:b)
62 !$omp end parallel do simd
67 !$omp parallel private (i)
68 !$omp cancellation point parallel
71 !$omp end critical (bar)
91 !$omp parallel do schedule(runtime) num_threads(8)
103 !$omp parallel sections firstprivate (b) if (.true.)
108 !$omp endparallelsections
112 !$omp parallel workshare num_threads (2)
115 !$omp end parallel workshare
120 !$omp task firstprivate (b)
124 !$omp task firstprivate (b)
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" } }