tree-optimization/113385 - wrong loop father with early exit vectorization
[official-gcc.git] / gcc / testsuite / gfortran.dg / gomp / workshare-reduction-27.f90
blob99a94f83faf1f270e5ca5da1175ac56828ba4417
1 ! { dg-do compile }
2 ! { dg-options "-O2 -fopenmp -fdump-tree-optimized" }
3 ! { dg-final { scan-tree-dump-times "__builtin_GOMP_loop(?:_ull)?_start \[^\n\r]*, (?:2147483648|-2147483648), 0, " 1 "optimized" } }
4 ! { dg-final { scan-tree-dump-times "__builtin_GOMP_loop_end " 1 "optimized" } }
5 ! { dg-final { scan-tree-dump-times "__builtin_GOMP_loop(?:_ull)?_runtime_next " 1 "optimized" } }
6 ! { dg-final { scan-tree-dump-times "__builtin_GOMP_workshare_task_reduction_unregister \\(0\\)" 1 "optimized" } }
7 ! { dg-final { scan-tree-dump-times "__builtin_GOMP_parallel " 1 "optimized" } }
9 module m
10 implicit none (type, external)
11 integer(8) :: j
12 interface
13 subroutine bar(i)
14 integer(8) :: i
15 end subroutine
16 end interface
17 end module m
19 subroutine foo(a, b, c)
20 use m
21 implicit none (type, external)
22 integer(8) :: a, b ,c
23 integer(8) :: i
24 !$omp parallel
25 !$omp do reduction (task, *: j) schedule (monotonic: runtime)
26 do i = a, b, c
27 j = j + 1
28 call bar (j)
29 end do
30 !$omp end parallel
31 end