1 ! RUN: %python %S/../test_errors.py %s %flang -fopenmp
3 ! Various checks with the ordered construct
5 SUBROUTINE LINEAR_GOOD(N
)
6 INTEGER N
, i
, j
, a
, b(10)
9 !$omp distribute parallel do simd linear(i)
13 !$omp end distribute parallel do simd
16 END SUBROUTINE LINEAR_GOOD
18 SUBROUTINE LINEAR_BAD(N
)
19 INTEGER N
, i
, j
, a
, b(10)
23 !ERROR: Variable 'j' not allowed in `LINEAR` clause, only loop iterator can be specified in `LINEAR` clause of a construct combined with `DISTRIBUTE`
24 !$omp distribute parallel do simd linear(j)
28 !$omp end distribute parallel do simd
34 !ERROR: Variable 'j' not allowed in `LINEAR` clause, only loop iterator can be specified in `LINEAR` clause of a construct combined with `DISTRIBUTE`
35 !ERROR: Variable 'b' not allowed in `LINEAR` clause, only loop iterator can be specified in `LINEAR` clause of a construct combined with `DISTRIBUTE`
36 !$omp distribute parallel do simd linear(j) linear(b)
40 !$omp end distribute parallel do simd
46 !ERROR: Variable 'j' not allowed in `LINEAR` clause, only loop iterator can be specified in `LINEAR` clause of a construct combined with `DISTRIBUTE`
47 !ERROR: Variable 'b' not allowed in `LINEAR` clause, only loop iterator can be specified in `LINEAR` clause of a construct combined with `DISTRIBUTE`
48 !$omp distribute parallel do simd linear(j, b)
52 !$omp end distribute parallel do simd
56 !ERROR: `DISTRIBUTE` region has to be strictly nested inside `TEAMS` region.
57 !ERROR: Variable 'j' not allowed in `LINEAR` clause, only loop iterator can be specified in `LINEAR` clause of a construct combined with `DISTRIBUTE`
58 !$omp distribute simd linear(i,j)
64 !$omp end distribute simd
66 !ERROR: `DISTRIBUTE` region has to be strictly nested inside `TEAMS` region.
67 !ERROR: Variable 'j' not allowed in `LINEAR` clause, only loop iterator can be specified in `LINEAR` clause of a construct combined with `DISTRIBUTE`
68 !$omp distribute simd linear(i,j) collapse(1)
74 !$omp end distribute simd
76 !ERROR: `DISTRIBUTE` region has to be strictly nested inside `TEAMS` region.
77 !$omp distribute simd linear(i,j) collapse(2)
83 !$omp end distribute simd
85 END SUBROUTINE LINEAR_BAD