tree-optimization/113385 - wrong loop father with early exit vectorization
[official-gcc.git] / gcc / testsuite / gfortran.dg / gomp / collapse1.f90
blob613f06f6ea9270cc9c874baf82583e1f909d5e95
1 ! { dg-do compile }
2 ! { dg-options "-fopenmp" }
4 subroutine collapse1
5 integer :: i, j, k, a(1:3, 4:6, 5:7)
6 real :: r
7 logical :: l
8 integer, save :: thr
9 !$omp threadprivate (thr)
10 l = .false.
11 a(:, :, :) = 0
12 !$omp parallel do collapse(4) schedule(static, 4) ! { dg-error "not enough DO loops for collapsed" }
13 do i = 1, 3
14 do j = 4, 6
15 do k = 5, 7
16 a(i, j, k) = i + j + k
17 end do
18 end do
19 end do
20 !$omp parallel do collapse(2)
21 do i = 1, 5, 2
22 do j = i + 1, 7, i ! { dg-error "loop increment not in canonical form" }
23 end do
24 end do
25 !$omp parallel do collapse(2) shared(j)
26 do i = 1, 3
27 do j = 4, 6 ! { dg-error "iteration variable present on clause other than PRIVATE, LASTPRIVATE or ALLOCATE" }
28 end do
29 end do
30 !$omp parallel do collapse(2)
31 do i = 1, 3
32 do j = 4, 6
33 end do
34 k = 4
35 end do
36 !$omp parallel do collapse(2) ! { dg-error "not enough DO loops" }
37 do i = 1, 3
39 end do
40 end do
41 !$omp parallel do collapse(2)
42 do i = 1, 3
43 do r = 4, 6 ! { dg-warning "must be integer" }
44 end do
45 end do
46 end subroutine collapse1
48 subroutine collapse1_2
49 integer :: i
50 !$omp parallel do collapse(2)
51 do i = -6, 6 ! { dg-error "cannot be redefined inside loop beginning" }
52 do i = 4, 6 ! { dg-error "iteration variable used in more than one loop|cannot be redefined" }
53 end do
54 end do
55 end subroutine collapse1_2
57 ! { dg-error "iteration variable must be of type integer" "integer" { target *-*-* } 43 }