xref: /llvm-project/flang/test/Semantics/OpenMP/linear-iter.f90 (revision 03cbe42627c7a7940b47cc1a2cda0120bc9c6d5e)
1! RUN: %python %S/../test_errors.py %s %flang -fopenmp
2! OpenMP Version 4.5
3! Various checks with the ordered construct
4
5SUBROUTINE LINEAR_GOOD(N)
6  INTEGER N, i, j, a, b(10)
7  !$omp target
8  !$omp teams
9  !$omp distribute parallel do simd linear(i)
10  do i = 1, N
11     a = 3.14
12  enddo
13  !$omp end distribute parallel do simd
14  !$omp end teams
15  !$omp end target
16END SUBROUTINE LINEAR_GOOD
17
18SUBROUTINE LINEAR_BAD(N)
19  INTEGER N, i, j, a, b(10)
20
21  !$omp target
22  !$omp teams
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)
25  do i = 1, N
26      a = 3.14
27  enddo
28  !$omp end distribute parallel do simd
29  !$omp end teams
30  !$omp end target
31
32  !$omp target
33  !$omp teams
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)
37  do i = 1, N
38     a = 3.14
39  enddo
40  !$omp end distribute parallel do simd
41  !$omp end teams
42  !$omp end target
43
44  !$omp target
45  !$omp teams
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)
49  do i = 1, N
50     a = 3.14
51  enddo
52  !$omp end distribute parallel do simd
53  !$omp end teams
54  !$omp end target
55
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)
59   do i = 1, N
60      do j = 1, N
61         a = 3.14
62      enddo
63   enddo
64   !$omp end distribute simd
65
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)
69   do i = 1, N
70      do j = 1, N
71         a = 3.14
72      enddo
73   enddo
74   !$omp end distribute simd
75
76   !ERROR: `DISTRIBUTE` region has to be strictly nested inside `TEAMS` region.
77   !$omp distribute simd linear(i,j) collapse(2)
78   do i = 1, N
79      do j = 1, N
80         a = 3.14
81      enddo
82   enddo
83   !$omp end distribute simd
84
85END SUBROUTINE LINEAR_BAD
86