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