tree-optimization/113385 - wrong loop father with early exit vectorization
[official-gcc.git] / gcc / testsuite / gfortran.dg / gomp / pr107214-4.f90
blobb4f343a17acc61ca4256448fcfaa473352f1b003
1 ! { dg-do compile }
2 ! { dg-additional-options "-fdump-tree-original" }
4 integer :: x, y
6 ! EXEC_OMP_TARGET_TEAMS
8 !$omp target teams map(x) firstprivate(x)
9 x = x + 1
10 !$omp end target teams
12 !$omp target teams map(x) firstprivate(y)
13 x = y + 1
14 !$omp end target teams
16 ! EXEC_OMP_TARGET_TEAMS_DISTRIBUTE
18 !$omp target teams distribute map(x) firstprivate(x)
19 do i=1,1
20 x = x + 1
21 end do
22 !$omp end target teams distribute
24 !$omp target teams distribute map(x) firstprivate(y)
25 do i=1,1
26 x = y + 1
27 end do
28 !$omp end target teams distribute
30 ! EXEC_OMP_TARGET_TEAMS_LOOP
32 !$omp target teams loop map(x) firstprivate(x)
33 do i=1,1
34 x = x + 1
35 end do
36 !$omp end target teams loop
38 !$omp target teams loop map(x) firstprivate(y)
39 do i=1,1
40 x = y + 1
41 end do
42 !$omp end target teams loop
44 ! EXEC_OMP_TARGET_TEAMS_DISTRIBUTE_SIMD
46 !$omp target teams distribute simd map(x) firstprivate(x)
47 do i=1,1
48 x = x + 1
49 end do
50 !$omp end target teams distribute simd
52 !$omp target teams distribute simd map(x) firstprivate(y)
53 do i=1,1
54 x = y + 1
55 end do
56 !$omp end target teams distribute simd
58 ! EXEC_OMP_TARGET_TEAMS_DISTRIBUTE_PARALLEL_DO
60 !$omp target teams distribute parallel do map(x) firstprivate(x)
61 do i=1,1
62 x = x + 1
63 end do
64 !$omp end target teams distribute parallel do
66 !$omp target teams distribute parallel do map(x) firstprivate(y)
67 do i=1,1
68 x = y + 1
69 end do
70 !$omp end target teams distribute parallel do
72 ! EXEC_OMP_TARGET_PARALLEL
74 !$omp target parallel map(x) firstprivate(x)
75 x = x + 1
76 !$omp end target parallel
78 !$omp target parallel map(x) firstprivate(y)
79 x = y + 1
80 !$omp end target parallel
82 ! EXEC_OMP_TARGET_PARALLEL_DO
84 !$omp target parallel do map(x) firstprivate(x)
85 do i=1,1
86 x = x + 1
87 end do
88 !$omp end target parallel do
90 !$omp target parallel do map(x) firstprivate(y)
91 do i=1,1
92 x = y + 1
93 end do
94 !$omp end target parallel do
96 ! EXEC_OMP_TARGET_PARALLEL_LOOP
98 !$omp target parallel loop map(x) firstprivate(x)
99 do i=1,1
100 x = x + 1
101 end do
102 !$omp end target parallel loop
104 !$omp target parallel loop map(x) firstprivate(y)
105 do i=1,1
106 x = y + 1
107 end do
108 !$omp end target parallel loop
110 ! EXEC_OMP_TARGET_PARALLEL_DO_SIMD
112 !$omp target parallel do simd map(x) firstprivate(x)
113 do i=1,1
114 x = x + 1
115 end do
116 !$omp end target parallel do simd
118 !$omp target parallel do simd map(x) firstprivate(y)
119 do i=1,1
120 x = y + 1
121 end do
122 !$omp end target parallel do simd
124 ! EXEC_OMP_TARGET_TEAMS_DISTRIBUTE_PARALLEL_DO_SIMD
126 !$omp target teams distribute parallel do simd map(x) firstprivate(x)
127 do i=1,1
128 x = x + 1
129 end do
130 !$omp end target teams distribute parallel do simd
132 !$omp target teams distribute parallel do simd map(x) firstprivate(y)
133 do i=1,1
134 x = y + 1
135 end do
136 !$omp end target teams distribute parallel do simd
138 ! { dg-final { scan-tree-dump-times {omp target map\(tofrom:x\)} 10 "original" } }
139 ! { dg-final { scan-tree-dump-times {omp target firstprivate\(y\) map\(tofrom:x\)} 10 "original" } }
141 ! { dg-final { scan-tree-dump-times {omp teams firstprivate\(x\)} 6 "original" } }
142 ! { dg-final { scan-tree-dump-times {omp teams firstprivate\(y\)} 6 "original" } }
144 ! { dg-final { scan-tree-dump-times {omp parallel firstprivate\(x\)} 6 "original" } }
145 ! { dg-final { scan-tree-dump-times {omp parallel firstprivate\(y\)} 6 "original" } }